Written run function
This commit is contained in:
parent
851568fa97
commit
7940a68150
1 changed files with 58 additions and 39 deletions
|
@ -2,6 +2,7 @@
|
||||||
|
|
||||||
module Interpreter where
|
module Interpreter where
|
||||||
import Data.Maybe (catMaybes)
|
import Data.Maybe (catMaybes)
|
||||||
|
import Control.Monad (liftM, ap)
|
||||||
|
|
||||||
data Instruction = TapeLeft | TapeRight | Add | Sub | Out | In | LoopStart | LoopEnd
|
data Instruction = TapeLeft | TapeRight | Add | Sub | Out | In | LoopStart | LoopEnd
|
||||||
deriving (Eq, Show)
|
deriving (Eq, Show)
|
||||||
|
@ -32,12 +33,26 @@ decr (Byte i) = Byte (i - 1)
|
||||||
type Tape = [Byte]
|
type Tape = [Byte]
|
||||||
type Program = [Instruction]
|
type Program = [Instruction]
|
||||||
|
|
||||||
data ProgState = ProgState {
|
data State = State {
|
||||||
tape :: Tape,
|
tape :: Tape,
|
||||||
dp :: Int,
|
dp :: Int,
|
||||||
output :: String,
|
output :: String,
|
||||||
program :: Program,
|
program :: Program,
|
||||||
ip :: Int }
|
ip :: Int } deriving (Show)
|
||||||
|
|
||||||
|
data Execution a = Working a | Crash Error | Done String deriving (Show)
|
||||||
|
|
||||||
|
instance Monad Execution where
|
||||||
|
(Crash e) >>= _ = Crash e
|
||||||
|
(Done t) >>= _ = Done t
|
||||||
|
(Working d) >>= f = f d
|
||||||
|
|
||||||
|
instance Functor Execution where
|
||||||
|
fmap = liftM
|
||||||
|
|
||||||
|
instance Applicative Execution where
|
||||||
|
pure = return
|
||||||
|
(<*>) = ap
|
||||||
|
|
||||||
toProgram :: String -> [Instruction]
|
toProgram :: String -> [Instruction]
|
||||||
toProgram s = catMaybes $ fmap parseInstr s
|
toProgram s = catMaybes $ fmap parseInstr s
|
||||||
|
@ -46,33 +61,33 @@ tapeHelp :: Tape -> Int -> (Byte -> Byte) -> Tape
|
||||||
tapeHelp (t:tt) 0 alter = alter t : tt
|
tapeHelp (t:tt) 0 alter = alter t : tt
|
||||||
tapeHelp (t:tt) dp alter = t : (tapeHelp tt dp alter)
|
tapeHelp (t:tt) dp alter = t : (tapeHelp tt dp alter)
|
||||||
|
|
||||||
data Error = NegTape | LoopNoMatch
|
data Error = NegTape | LoopNoMatch deriving (Show)
|
||||||
|
|
||||||
errorDesc :: Error -> String
|
errorDesc :: Error -> String
|
||||||
errorDesc NegTape = "ERROR: '<' not working. Cannot access negative tape positions."
|
errorDesc NegTape = "ERROR: '<' not working. Cannot access negative tape positions."
|
||||||
errorDesc LoopNoMatch = "ERROR: '[' or ']' not working. Matching parenthesis not found."
|
errorDesc LoopNoMatch = "ERROR: '[' or ']' not working. Matching parenthesis not found."
|
||||||
|
|
||||||
incrIP :: ProgState -> ProgState
|
incrIP :: State -> State
|
||||||
incrIP p = p { ip = ip p + 1 }
|
incrIP p = p { ip = ip p + 1 }
|
||||||
|
|
||||||
execAdd :: ProgState -> Either Error ProgState
|
execAdd :: State -> Execution State
|
||||||
execAdd p = Right p { tape = newTape }
|
execAdd p = Working p { tape = newTape }
|
||||||
where newTape = tapeHelp (tape p) (dp p) incr
|
where newTape = tapeHelp (tape p) (dp p) incr
|
||||||
|
|
||||||
execSub :: ProgState -> Either Error ProgState
|
execSub :: State -> Execution State
|
||||||
execSub p = Right p { tape = newTape }
|
execSub p = Working p { tape = newTape }
|
||||||
where newTape = tapeHelp (tape p) (dp p) decr
|
where newTape = tapeHelp (tape p) (dp p) decr
|
||||||
|
|
||||||
execTapeLeft :: ProgState -> Either Error ProgState
|
execTapeLeft :: State -> Execution State
|
||||||
execTapeLeft p = case dp p of 0 -> Left NegTape
|
execTapeLeft p = case dp p of 0 -> Crash NegTape
|
||||||
n -> Right p { dp = n - 1 }
|
n -> Working p { dp = n - 1 }
|
||||||
|
|
||||||
execTapeRight :: ProgState -> Either Error ProgState
|
execTapeRight :: State -> Execution State
|
||||||
execTapeRight p = Right p { tape = if endOfType then tape p ++ [Byte 0] else tape p }
|
execTapeRight p = Working p { tape = if endOfType then tape p ++ [Byte 0] else tape p }
|
||||||
where endOfType = dp p == length (tape p) - 1
|
where endOfType = dp p == length (tape p) - 1
|
||||||
|
|
||||||
execOut :: ProgState -> Either Error ProgState
|
execOut :: State -> Execution State
|
||||||
execOut p = Right p { output = output p ++ [chr char]}
|
execOut p = Working p { output = output p ++ [chr char]}
|
||||||
where char = (tape p) !! dp p
|
where char = (tape p) !! dp p
|
||||||
|
|
||||||
data WalkingDirection = Forward | Backward
|
data WalkingDirection = Forward | Backward
|
||||||
|
@ -91,35 +106,39 @@ findMatching prg start wd = case wd of
|
||||||
| otherwise = fmHelper (upd s) acc b ob upd limit
|
| otherwise = fmHelper (upd s) acc b ob upd limit
|
||||||
where c = prg !! start
|
where c = prg !! start
|
||||||
|
|
||||||
execLoop :: WalkingDirection -> ProgState -> Either Error ProgState
|
execLoop :: WalkingDirection -> State -> Execution State
|
||||||
execLoop d w = case posOrF of
|
execLoop d w = case posOrF of
|
||||||
Just n -> Right w { ip = n }
|
Just n -> Working w { ip = n }
|
||||||
Nothing -> Left LoopNoMatch
|
Nothing -> Crash LoopNoMatch
|
||||||
where jump = (tape w !! dp w) == Byte 0
|
where jump = (tape w !! dp w) == Byte 0
|
||||||
posOrF = if jump then findMatching (program w) (ip w) d else Just $ ip w
|
posOrF = if jump then findMatching (program w) (ip w) d else Just $ ip w
|
||||||
|
|
||||||
executeInstruction :: Instruction -> ProgState -> Either Error ProgState
|
execute :: State -> Execution State
|
||||||
executeInstruction w = (fmap incrIP) . case (program w !! ip w) of
|
execute w = runInstr w >>= checkDone >>= execute
|
||||||
TapeLeft -> execTapeLeft
|
where instrFor w = case (program w !! ip w) of
|
||||||
TapeRight -> execTapeRight
|
TapeLeft -> execTapeLeft
|
||||||
Add -> execAdd
|
TapeRight -> execTapeRight
|
||||||
Sub -> execSub
|
Add -> execAdd
|
||||||
Out -> execOut
|
Sub -> execSub
|
||||||
LoopStart -> execLoop Forward
|
Out -> execOut
|
||||||
LoopEnd -> execLoop Backward $ w
|
LoopStart -> execLoop Forward
|
||||||
|
LoopEnd -> execLoop Backward
|
||||||
|
|
||||||
newtype Executor a = Ee Either String a
|
runInstr :: State -> Execution State
|
||||||
instance Executor Monad where
|
runInstr w = instrFor w $ w
|
||||||
`<<=` :: Executor a -> (a -> Executor a) -> Executor A
|
|
||||||
(Ee a) <<= k = case a of
|
|
||||||
Left c -> Ee (Left c)
|
|
||||||
Right b -> k
|
|
||||||
return :: a -> Executor a
|
|
||||||
return a = Ee (Left a)
|
|
||||||
fail :: String -> Executor a
|
|
||||||
fail c = Ee (Right c)
|
|
||||||
|
|
||||||
executeInstruction
|
|
||||||
|
|
||||||
|
checkDone :: State -> Execution State
|
||||||
|
checkDone ps
|
||||||
|
| length (program ps) == ip ps = Done $ output ps
|
||||||
|
| otherwise = Working $ incrIP ps
|
||||||
|
|
||||||
|
initState :: Program -> State
|
||||||
|
initState p = State {
|
||||||
|
tape = [Byte 0],
|
||||||
|
dp = 0,
|
||||||
|
output = "",
|
||||||
|
program = p,
|
||||||
|
ip = 0}
|
||||||
|
|
||||||
|
run :: String -> Execution State
|
||||||
|
run = execute . initState . catMaybes . fmap parseInstr
|
||||||
|
|
Loading…
Reference in a new issue