Implemented OUT and reimplemented IN with IO

This commit is contained in:
Claudio Maggioni (maggicl) 2020-10-31 23:45:03 +01:00
parent 4dc1eeb3c3
commit 5f8a2cadf3

View file

@ -35,15 +35,14 @@ type Program = [Instruction]
data State = State { data State = State {
tape :: Tape, tape :: Tape,
dp :: Int, dp :: Int,
output :: String,
program :: Program, program :: Program,
ip :: Int } deriving (Show) ip :: Int } deriving (Show)
data Execution a = Working a | Crash Error | Done String deriving (Show) data Execution a = Working a | Crash Error | Done deriving (Show)
instance Monad Execution where instance Monad Execution where
(Crash e) >>= _ = Crash e (Crash e) >>= _ = Crash e
(Done t) >>= _ = Done t Done >>= _ = Done
(Working d) >>= f = f d (Working d) >>= f = f d
instance Functor Execution where instance Functor Execution where
@ -69,35 +68,39 @@ errorDesc LoopNoMatch = "ERROR: '[' or ']' not working. Matching parenthesis not
incrIP :: State -> State incrIP :: State -> State
incrIP p = p { ip = ip p + 1 } incrIP p = p { ip = ip p + 1 }
execUpdate :: Instruction -> State -> Execution State execUpdate :: Instruction -> State -> State
execUpdate i p = Working p { tape = newTape } execUpdate i p = p { tape = newTape }
where newTape = tapeHelp (tape p) (dp p) (updateCell i) where newTape = tapeHelp (tape p) (dp p) (updateCell i)
execTapeLeft :: State -> Execution State execTapeLeft :: State -> Execution State
execTapeLeft p = case dp p of 0 -> Crash NegTape execTapeLeft p = case dp p of 0 -> Crash NegTape
n -> Working p { dp = n - 1 } n -> Working p { dp = n - 1 }
execTapeRight :: State -> Execution State execTapeRight :: State -> State
execTapeRight p = Working p { tape = tape p ++ newTape, dp = dp p + 1 } execTapeRight p = p { tape = tape p ++ newTape, dp = dp p + 1 }
where newTape = case dp p == length (tape p) - 1 of True -> [Byte 0] where newTape = case dp p == length (tape p) - 1 of True -> [Byte 0]
_ -> [] _ -> []
execOut :: State -> Execution State execIn :: State -> IO (Execution State)
execOut p = Working p { output = output p ++ [chr char]} execIn p = do chr <- getChar
where char = tape p !! dp p tp <- pure $ fromEnum chr
return $ Working p { tape = tapeHelp (tape p) (dp p) (\_ -> Byte tp) }
execOut :: State -> IO (Execution State)
execOut p = putChar (chr (tape p !! dp p)) >> (return . Working $ p)
findMatching :: Program -> Instruction -> Int -> Maybe Int findMatching :: Program -> Instruction -> Int -> Maybe Int
findMatching prg toFind = fmHelper $ -1 findMatching prg par = fmHelper $ -1
where (oppos, limit, next) = case toFind of where (oppos, limit, next) = case par of
LoopEnd -> (LoopStart, length prg, (+1)) LoopStart -> (LoopEnd, length prg, (+1))
LoopStart -> (LoopEnd, 0, (-1+)) LoopEnd -> (LoopStart, 0, (-1+))
fmHelper :: Int -> Int -> Maybe Int fmHelper :: Int -> Int -> Maybe Int
fmHelper acc s fmHelper acc s
| s == limit = Nothing | s == limit = Nothing
| acc == 0 && c == toFind = Just s | acc == 0 && c == oppos = Just s
| c == toFind = fmHelper (acc - 1) $ next s | c == oppos = fmHelper (acc - 1) $ next s
| c == oppos = fmHelper (acc + 1) $ next s | c == par = fmHelper (acc + 1) $ next s
| otherwise = fmHelper acc $ next s | otherwise = fmHelper acc $ next s
where c = prg !! s where c = prg !! s
@ -110,35 +113,40 @@ execLoop d w = case posOrF of Just n -> Working w { ip = n }
posOrF = case jump of True -> findMatching (program w) d (ip w) posOrF = case jump of True -> findMatching (program w) d (ip w)
_ -> Just $ ip w _ -> Just $ ip w
execute :: State -> Execution State execute :: State -> IO (Execution State)
execute w = do ran <- (traceShowId $ runInstr w) execute w = runInstr w >>= andThen
newStatus <- checkDone ran where instrFor :: State -> State -> IO (Execution State)
execute newStatus instrFor w = case (program w !! ip w) of
where instrFor w = case (program w !! ip w) of TapeLeft -> return . execTapeLeft
TapeLeft -> execTapeLeft TapeRight -> return . Working . execTapeRight
TapeRight -> execTapeRight Add -> return . Working . (execUpdate Add)
Add -> execUpdate Add Sub -> return . Working . (execUpdate Sub)
Sub -> execUpdate Sub In -> execIn
Out -> execOut Out -> execOut
l -> execLoop l l -> return . execLoop l
runInstr :: State -> Execution State andThen :: Execution State -> IO (Execution State)
andThen s = case s >>= checkDone of
Working s -> execute s
t -> return t
runInstr :: State -> IO (Execution State)
runInstr w = instrFor w $ w runInstr w = instrFor w $ w
checkDone :: State -> Execution State checkDone :: State -> Execution State
checkDone ps checkDone ps
| (length . program) ps == newIP = Done $ output ps | (length . program) ps == newIP = Done
| otherwise = Working $ ps { ip = newIP } | otherwise = Working $ ps { ip = newIP }
where newIP = ip ps + 1 where newIP = ip ps + 1
initState :: Program -> State initState :: Program -> State
initState p = State { initState p = State {
tape = [Byte 0], tape = [Byte 0],
dp = 0, dp = 0,
output = "",
program = p, program = p,
ip = 0} ip = 0}
run :: String -> Execution State run :: String -> IO (Execution State)
run "" = Done "" run s = case catMaybes . fmap parseInstr $ s of [] -> return Done
run s = execute . initState . catMaybes . fmap parseInstr $ s l -> execute . initState $ l