diff --git a/app/MainOptions.hs b/app/MainOptions.hs
index af1bfe291f20565aaf6a48257dac9467214e5b66..18fd5e2db5342a522cd107ad114ae01304b89975 100644
--- a/app/MainOptions.hs
+++ b/app/MainOptions.hs
@@ -7,8 +7,7 @@ import           Control.Applicative
 data MainOptions = MainOptions
     {
         input :: String,
-        output :: String,
-        verbose :: Bool
+        output :: String
     }
 
 
@@ -29,5 +28,4 @@ instance Options MainOptions where
                              , optionShortFlags  = ['o']
                              , optionDescription = "Compiled file output"
                              }
-                    )
-            <*> simpleOption "v" False "Be more verbose"
+                    )
\ No newline at end of file
diff --git a/package.yaml b/package.yaml
index 90e28e273938411bfd471c4317f71d7110fe27e3..3d7be364011142999e4a94d35802eead8f6d903b 100644
--- a/package.yaml
+++ b/package.yaml
@@ -13,6 +13,7 @@ tests:
 copyright: 2020 Author name here
 maintainer: example@example.com
 dependencies:
+- mtl >= 2.2.2 && < 3
 - trifecta >= 2 && < 3
 - base >= 4.7 && < 5
 - parsers >= 0.12 && < 1
diff --git a/src/CodeGenerator.hs b/src/CodeGenerator.hs
index 8fe4b10672769b3e646dad04746a7c4b919733c7..886bc9c581220e8346a4bbebaacd1c0f27144f05 100644
--- a/src/CodeGenerator.hs
+++ b/src/CodeGenerator.hs
@@ -1,10 +1 @@
-module CodeGenerator where
-
-import           Definitions
-
-data State = State {
-    parsed :: BrainBreakBlock,
-    unparsed :: BrainBreakBlock,
-    mainFunction :: String
-}
-
+module CodeGenerator where
\ No newline at end of file
diff --git a/src/Definitions.hs b/src/Definitions.hs
index 0e5bec49e16e343c9d0906cd54ac1ad4c71012f6..25b7c40925c38ece9a0eaa91034e90d0d0fb34ce 100644
--- a/src/Definitions.hs
+++ b/src/Definitions.hs
@@ -11,3 +11,7 @@ data BrainBreakOperation = Increment
     deriving (Eq, Show)
 
 type BrainBreakBlock = [BrainBreakOperation]
+
+data REPLHelpers = PrintState  deriving (Show)
+
+data REPLCode = Code BrainBreakBlock | Helper REPLHelpers  deriving (Show)
diff --git a/src/LangParser.hs b/src/LangParser.hs
index 5327a87bc564325e2e702408923c8676d4982dc3..6e191e1c9bb7b1c63d3dd02522e197b2786dcbd9 100644
--- a/src/LangParser.hs
+++ b/src/LangParser.hs
@@ -7,6 +7,7 @@ import           Text.Parser.Combinators
 import           Text.Parser.Token
 import           Data.Functor
 
+-- Remove all comments from code. With recursive Loop code cleaning
 filterComments :: BrainBreakBlock -> BrainBreakBlock
 filterComments (Comment : ops) = [] ++ filterComments ops
 filterComments (Loop ops : otherCode) =
@@ -40,3 +41,13 @@ parseBrainBreak =
     parseRight     = symbolic '>' $> MoveRight
     parseIncrement = symbolic '+' $> Increment
     parseDecrement = symbolic '-' $> Decrement
+
+parseReplHelpers :: Parser REPLHelpers
+parseReplHelpers = parsePrintState
+    where parsePrintState = symbol ":state" $> PrintState
+
+parseREPLCode :: Parser REPLCode
+parseREPLCode = 
+    Helper <$> parseReplHelpers 
+    <|> Code <$> parseBrainBreak
+        
diff --git a/src/Lib.hs b/src/Lib.hs
index f78bb063cb8e145c68ec9fdd5b253ed9efb57b08..978eebd8cd4d43c21753a89500b63c8fcfa36d68 100644
--- a/src/Lib.hs
+++ b/src/Lib.hs
@@ -1,5 +1,6 @@
 module Lib where
 
+import           REPL
 import           LangParser
 import           Definitions
 import           Text.Trifecta
@@ -8,9 +9,9 @@ import           Data.List
 startRepl :: IO ()
 startRepl = do
     input <- getLine
-    let parsed_string = parseString parseBrainBreak mempty input
+    let parsed_string = parseString parseREPLCode mempty input
     case parsed_string of
-        Success code -> print (filterComments code)
+        Success code -> runReplCode code
         Failure info -> print (_errDoc info)
     startRepl
 
@@ -23,10 +24,4 @@ runFile filename = do
 
 
 compileFile :: String -> String -> IO ()
-compileFile input output = putStrLn "Compiling code in unavailable."
-
-run :: [String] -> IO ()
-run args = case args of
-    [] -> startRepl
-    [x] -> runFile x
-    (inFile : _ : "-o" : outFile : _) -> compileFile inFile outFile
+compileFile input output = putStrLn "Compiling code developing is in progress."
diff --git a/src/REPL.hs b/src/REPL.hs
new file mode 100644
index 0000000000000000000000000000000000000000..131fb5aa24b06fe716df7deab874841b8938abf4
--- /dev/null
+++ b/src/REPL.hs
@@ -0,0 +1,71 @@
+module REPL where
+
+import           Control.Monad.State
+import           Definitions
+
+data REPLState = REPLState{
+    buffer :: [Integer],
+    index :: Integer,
+    offset :: Integer
+} deriving (Show)
+
+data Direction =
+    LeftDirection | RightDirection
+    deriving (Eq, Show)
+
+
+-- Initial buffer length and expanding rate
+replicaFactor :: Int
+replicaFactor = 3000
+
+defaultState :: REPLState
+defaultState =
+    REPLState { buffer = replicate replicaFactor 0, index = 0, offset = 0 }
+
+expandIfNeeded :: [Integer] -> Integer -> [Integer]
+-- Expand buffer to travel left but index is less than zero
+expandIfNeeded old_buffer (-1)      = replicate replicaFactor 0 ++ old_buffer
+-- Expand buffer in need to travel Right
+expandIfNeeded old_buffer new_index = old_buffer
+    ++ needed (new_index - toInteger (length old_buffer))
+  where
+    needed len | len >= 0 = replicate replicaFactor 0
+               | len < 0  = []
+
+-- Fuction to update state accordingly to walk direction
+walkUpdate :: Direction -> REPLState -> REPLState
+-- Walk left with buffer expnding if needed
+walkUpdate LeftDirection old_state  = do
+    let update_func t = t - 1
+    let updated_buffer =
+            expandIfNeeded (buffer old_state) (update_func $ index old_state)
+    -- Finding diff because we need to update current index correctly
+    let len_diff =
+            toInteger $ length updated_buffer - length (buffer old_state)
+    REPLState { buffer = updated_buffer
+              , index  = update_func $ index old_state + len_diff
+              , offset = update_func $ offset old_state
+              }
+
+walkUpdate RightDirection old_state  = do
+    let update_func t = t + 1
+    let updated_buffer =
+            expandIfNeeded (buffer old_state) (update_func $ index old_state)
+    REPLState { buffer = updated_buffer
+              , index  = update_func $ index old_state
+              , offset = update_func $ offset old_state
+              }
+
+walk :: Direction -> State REPLState ()
+walk direction = do
+    modify (walkUpdate direction)
+    return ()
+
+doAction :: REPLCode -> State REPLState ()
+doAction = undefined
+
+runHelper :: REPLHelpers -> State REPLState ()
+runHelper = undefined
+
+runReplCode :: REPLCode -> IO ()
+runReplCode = undefined
\ No newline at end of file
diff --git a/test.bf b/test.bf
new file mode 100644
index 0000000000000000000000000000000000000000..609fbfe290c7474cf529816bf7b48f7119069b49
--- /dev/null
+++ b/test.bf
@@ -0,0 +1,2 @@
+This is test file to check how parser works;
+<++[-_-]++>