From fcd428f51762ee16830625bb9ba7d8608785ef64 Mon Sep 17 00:00:00 2001 From: Pavel Kirilin <win10@list.ru> Date: Tue, 16 Jun 2020 03:40:33 +0400 Subject: [PATCH] Fixed structure. Description: - REPL module moved in Interpreter namespace. - Created Parser namespace. - Added plans for optimizer. Signed-off-by: Pavel Kirilin <win10@list.ru> --- app/Main.hs | 2 +- package.yaml | 3 +- src/{REPL.hs => Interpreter/Interpreter.hs} | 66 +++++++-------------- src/Interpreter/Optimizer.hs | 32 ++++++++++ src/Interpreter/REPL.hs | 32 ++++++++++ src/Lib.hs | 7 ++- src/{ => Parser}/Definitions.hs | 2 +- src/{ => Parser}/LangParser.hs | 13 ++-- 8 files changed, 101 insertions(+), 56 deletions(-) rename src/{REPL.hs => Interpreter/Interpreter.hs} (75%) create mode 100644 src/Interpreter/Optimizer.hs create mode 100644 src/Interpreter/REPL.hs rename src/{ => Parser}/Definitions.hs (92%) rename src/{ => Parser}/LangParser.hs (96%) diff --git a/app/Main.hs b/app/Main.hs index 0da7cc9..5c6c29f 100644 --- a/app/Main.hs +++ b/app/Main.hs @@ -1,9 +1,9 @@ module Main where import Lib -import REPL import Options import MainOptions +import Interpreter.REPL import System.Environment main :: IO () diff --git a/package.yaml b/package.yaml index 3d7be36..77952a0 100644 --- a/package.yaml +++ b/package.yaml @@ -1,5 +1,6 @@ library: - source-dirs: src + source-dirs: + - src tests: brainBreak-test: source-dirs: test diff --git a/src/REPL.hs b/src/Interpreter/Interpreter.hs similarity index 75% rename from src/REPL.hs rename to src/Interpreter/Interpreter.hs index bc9a3a2..8fe81cd 100644 --- a/src/REPL.hs +++ b/src/Interpreter/Interpreter.hs @@ -1,12 +1,13 @@ -module REPL where +module Interpreter.Interpreter where -import LangParser -import Definitions +import System.IO import Text.Trifecta +import Parser.LangParser +import Parser.Definitions import Control.Monad.State -import System.IO -data REPLState = REPLState{ + +data InterpreterState = InterpreterState{ buffer :: [Integer], inputNumber :: Integer, index :: Integer, @@ -22,7 +23,7 @@ data Direction = replicaFactor :: Int replicaFactor = 3000 -io :: IO a -> StateT REPLState IO a +io :: IO a -> StateT InterpreterState IO a io = liftIO prompt :: String -> IO String @@ -31,8 +32,8 @@ prompt text = do hFlush stdout getLine -defaultState :: REPLState -defaultState = REPLState { buffer = replicate replicaFactor 0 +defaultState :: InterpreterState +defaultState = InterpreterState { buffer = replicate replicaFactor 0 , inputNumber = 0 , index = 0 , offset = 0 @@ -54,11 +55,11 @@ expandIfNeeded old_buffer new_index = old_buffer needed len | len >= 0 = replicate replicaFactor 0 | len < 0 = [] -increaseInputNumber :: REPLState -> REPLState +increaseInputNumber :: InterpreterState -> InterpreterState increaseInputNumber state = state { inputNumber = inputNumber state + 1 } -- Fuction to update state accordingly to walk direction -walkUpdate :: Direction -> REPLState -> REPLState +walkUpdate :: Direction -> InterpreterState -> InterpreterState -- Walk left with buffer expnding if needed walkUpdate LeftDirection old_state = do let update_func t = t - 1 @@ -81,22 +82,22 @@ walkUpdate RightDirection old_state = do , offset = update_func $ offset old_state } -updateStateCell :: (Integer -> Integer) -> REPLState -> REPLState +updateStateCell :: (Integer -> Integer) -> InterpreterState -> InterpreterState updateStateCell update_func old_state = do let new_buffer = updateListElement (buffer old_state) (index old_state) update_func old_state{ buffer = new_buffer } -updateCell :: (Integer->Integer) -> StateT REPLState IO () +updateCell :: (Integer->Integer) -> StateT InterpreterState IO () updateCell update_func = modify (updateStateCell update_func) -walk :: Direction -> StateT REPLState IO () +walk :: Direction -> StateT InterpreterState IO () walk direction = do modify (walkUpdate direction) return () -doAction :: REPLCode -> State REPLState () +doAction :: REPLCode -> State InterpreterState () doAction = undefined @@ -106,7 +107,7 @@ getBufferSlice size current_index current_buffer = do let end = fromInteger $ current_index + size drop start $ take end current_buffer -runHelper :: REPLHelpers -> StateT REPLState IO () +runHelper :: REPLHelpers -> StateT InterpreterState IO () runHelper PrintState = do current_state <- get let buffer_slice = getBufferSlice 5 (index current_state) (buffer current_state) @@ -127,25 +128,25 @@ runHelper PrintBufChars = do io $ print $ map (\t -> toEnum (fromInteger t) :: Char) buffer_slice return () -getCell :: StateT REPLState IO Integer +getCell :: StateT InterpreterState IO Integer getCell = do state <- get return $ buffer state !! fromInteger (index state) -printCell :: StateT REPLState IO () +printCell :: StateT InterpreterState IO () printCell = do cell <- getCell io $ putChar (toEnum (fromInteger cell) :: Char) io $ hFlush stdout return () -readCell :: StateT REPLState IO () +readCell :: StateT InterpreterState IO () readCell = do char <- io getChar updateCell (const $ toInteger $ fromEnum char) return () -runBrainCodeLoop :: BrainBreakBlock -> StateT REPLState IO () +runBrainCodeLoop :: BrainBreakBlock -> StateT InterpreterState IO () runBrainCodeLoop code = do cell <- getCell case cell of @@ -156,7 +157,7 @@ runBrainCodeLoop code = do 0 -> return () val -> runBrainCodeLoop code -runBrainBreakOperation :: BrainBreakOperation -> StateT REPLState IO () +runBrainBreakOperation :: BrainBreakOperation -> StateT InterpreterState IO () runBrainBreakOperation MoveLeft = walk LeftDirection runBrainBreakOperation MoveRight = walk RightDirection runBrainBreakOperation Increment = updateCell (+1) @@ -166,31 +167,8 @@ runBrainBreakOperation Read = readCell runBrainBreakOperation (Loop code) = runBrainCodeLoop code runBrainBreakOperation Comment = return () -runBrainBreakCode :: BrainBreakBlock -> StateT REPLState IO () +runBrainBreakCode :: BrainBreakBlock -> StateT InterpreterState IO () runBrainBreakCode (x : xs) = do runBrainBreakOperation x runBrainBreakCode xs runBrainBreakCode [] = return () - - -replCodeRunner :: REPLCode -> StateT REPLState IO () -replCodeRunner code = case code of - Helper helper -> runHelper helper - Code bb_code -> runBrainBreakCode $ filterComments bb_code - -runREPL :: StateT REPLState IO () -runREPL = do - state <- get - io $ putStr $ "\nIn [" ++ show (inputNumber state) ++ "]: " - io $ hFlush stdout - input <- io getLine - let code = parseString parseREPLCode mempty input - case code of - Success code -> replCodeRunner code - Failure info -> io $ print (_errDoc info) - modify increaseInputNumber - runREPL - - -startREPL :: IO () -startREPL = evalStateT runREPL defaultState \ No newline at end of file diff --git a/src/Interpreter/Optimizer.hs b/src/Interpreter/Optimizer.hs new file mode 100644 index 0000000..66af1c1 --- /dev/null +++ b/src/Interpreter/Optimizer.hs @@ -0,0 +1,32 @@ +module Interpreter.Optimizer where + +{- +Optiomization plans: + * Instruction merging + * Efficient cell zeroing + * Dead code elimination + * Instruction conversion + + ## Insstruction merging + Precalculate the result of operation brefore compile/During interpreting. + +++ --- ++ => ++ + +++ --- --- => --- + >>> << => > + > <<<< => <<<< + +++ --- => Deletes operation + +## Efficient cell zeroing + [-] -> Set current cell to zero + +## Dead code elimination + Because the next cell is probably zero, delete the second loop. + Maybe this check is unnecesary. + [+>][<-] => [+>] + Also remove Loops at the begining of the programm. + +## Instruction conversion + Just for efficency + [-]+++ => Set 0, Add 3 => Set 3 + +++[-] => Set 0 + Also sequential Set instructions may be merged. +-} \ No newline at end of file diff --git a/src/Interpreter/REPL.hs b/src/Interpreter/REPL.hs new file mode 100644 index 0000000..a05b28a --- /dev/null +++ b/src/Interpreter/REPL.hs @@ -0,0 +1,32 @@ +module Interpreter.REPL where + +import System.IO +import Text.Trifecta +import Parser.LangParser +import Parser.Definitions +import Control.Monad.State +import Interpreter.Interpreter + + + +replCodeRunner :: REPLCode -> StateT InterpreterState IO () +replCodeRunner code = case code of + Helper helper -> runHelper helper + Code bb_code -> runBrainBreakCode $ filterComments bb_code + +runREPL :: StateT InterpreterState IO () +runREPL = do + state <- get + io $ putStr $ "\nIn [" ++ show (inputNumber state) ++ "]: " + io $ hFlush stdout + input <- io getLine + let code = parseString parseREPLCode mempty input + case code of + Success code -> replCodeRunner code + Failure info -> io $ print (_errDoc info) + modify increaseInputNumber + runREPL + + +startREPL :: IO () +startREPL = evalStateT runREPL defaultState \ No newline at end of file diff --git a/src/Lib.hs b/src/Lib.hs index be98d25..000c702 100644 --- a/src/Lib.hs +++ b/src/Lib.hs @@ -1,11 +1,12 @@ module Lib where -import REPL import Data.List -import LangParser -import Definitions import Text.Trifecta +import Interpreter.REPL +import Parser.LangParser +import Parser.Definitions import Control.Monad.State +import Interpreter.Interpreter runFile :: String -> IO () diff --git a/src/Definitions.hs b/src/Parser/Definitions.hs similarity index 92% rename from src/Definitions.hs rename to src/Parser/Definitions.hs index 56cfcad..da365b2 100644 --- a/src/Definitions.hs +++ b/src/Parser/Definitions.hs @@ -1,4 +1,4 @@ -module Definitions where +module Parser.Definitions where data BrainBreakOperation = Increment diff --git a/src/LangParser.hs b/src/Parser/LangParser.hs similarity index 96% rename from src/LangParser.hs rename to src/Parser/LangParser.hs index aa3c0cc..7d870ed 100644 --- a/src/LangParser.hs +++ b/src/Parser/LangParser.hs @@ -1,11 +1,12 @@ -module LangParser where -import Control.Applicative -import Text.Trifecta +module Parser.LangParser where + import Data.Maybe ( catMaybes ) -import Definitions -import Text.Parser.Combinators -import Text.Parser.Token import Data.Functor +import Text.Trifecta +import Text.Parser.Token +import Parser.Definitions +import Control.Applicative +import Text.Parser.Combinators -- Remove all comments from code. With recursive Loop code cleaning filterComments :: BrainBreakBlock -> BrainBreakBlock -- GitLab