Skip to content
Snippets Groups Projects
Unverified Commit 2d9cc0dd authored by Pavel Kirilin's avatar Pavel Kirilin :alien:
Browse files

Fixed language parser.


Signed-off-by: default avatarPavel Kirilin <win10@list.ru>
parent bee08683
No related merge requests found
module CodeGenerator where
import Definitions
data State = State {
parsed :: BrainBreakBlock,
unparsed :: BrainBreakBlock,
mainFunction :: String
}
...@@ -6,6 +6,7 @@ data BrainBreakOperation = Increment ...@@ -6,6 +6,7 @@ data BrainBreakOperation = Increment
| MoveLeft | MoveLeft
| Read | Read
| Write | Write
| Comment
| Loop BrainBreakBlock | Loop BrainBreakBlock
deriving (Eq, Show) deriving (Eq, Show)
......
module Lexer where module LangParser where
import Control.Applicative import Control.Applicative
import Text.Trifecta import Text.Trifecta
import Data.Maybe (catMaybes)
import Definitions import Definitions
import Text.Parser.Combinators import Text.Parser.Combinators
import Text.Parser.Token import Text.Parser.Token
import Data.Functor import Data.Functor
filterComments :: BrainBreakBlock -> BrainBreakBlock
filterComments (Comment:ops) = [] ++ filterComments ops
filterComments (Loop ops:otherCode) = Loop (filterComments ops) : filterComments otherCode
filterComments (op:ops) = op : filterComments ops
filterComments [] = []
parseComments :: Parser BrainBreakOperation
parseComments = satisfy (not . (`elem` "<+>-[],.")) $> Comment
parseLoop :: Parser BrainBreakOperation
parseLoop = do
expr <- brackets parseBrainBreak
pure $ Loop expr
parseBrainBreak :: Parser BrainBreakBlock parseBrainBreak :: Parser BrainBreakBlock
parseBrainBreak = many $ parseLeft parseBrainBreak = many $ parseLeft
<|> parseRight <|> parseRight
...@@ -14,13 +29,11 @@ parseBrainBreak = many $ parseLeft ...@@ -14,13 +29,11 @@ parseBrainBreak = many $ parseLeft
<|> parseRead <|> parseRead
<|> parseWrite <|> parseWrite
<|> parseLoop <|> parseLoop
<|> parseComments
where where
parseRead = comma $> Read parseRead = comma $> Read
parseWrite = dot $> Write parseWrite = dot $> Write
parseLeft = symbolic '<' $> MoveLeft parseLeft = symbolic '<' $> MoveLeft
parseRight = symbolic '>' $> MoveRight parseRight = symbolic '>' $> MoveRight
parseIncrement = symbolic '+' $> Increment parseIncrement = symbolic '+' $> Increment
parseDecrement = symbolic '-' $> Decrement parseDecrement = symbolic '-' $> Decrement
parseLoop = do \ No newline at end of file
expr <- brackets parseBrainBreak
pure $ Loop expr
module Lib where module Lib where
import Lexer import LangParser
import Definitions
import Text.Trifecta import Text.Trifecta
parseLine :: String -> IO () parseLine :: String -> IO ()
parseLine line = case parseString parseBrainBreak mempty line of parseLine line = case parseString parseBrainBreak mempty line of
Success code -> print $ show code Success code -> print $ show $ filterComments code
Failure info -> print $ _errDoc info Failure info -> print $ _errDoc info
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment