Skip to content

Commit

Permalink
feat(parser): unnecessary program declaration and statements braces
Browse files Browse the repository at this point in the history
  • Loading branch information
vorotynsky committed Nov 11, 2021
1 parent 8badef8 commit f3324af
Show file tree
Hide file tree
Showing 15 changed files with 172 additions and 140 deletions.
5 changes: 0 additions & 5 deletions src/Kroha/Errors.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,11 +49,6 @@ toErrorList = concatMap mapper
mapper error = [error]


sNub :: Eq a => [a] -> [a]
sNub (a:b:tail) | a == b = sNub (b:tail)
| otherwise = a:sNub (b:tail)
sNub xs = xs

showErrors :: (NodeId -> Maybe (SourcePos, SourcePos)) -> Error -> String
showErrors findRange = intercalate "\n" . fmap (uncurry showError) . process . toErrorList . pure
where showError _ (JoinedError _) = undefined
Expand Down
5 changes: 4 additions & 1 deletion src/Kroha/Parser/Declarations.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@ import Kroha.Syntax (Declaration(..), Program (Program))
import Text.Megaparsec
import Data.Bifunctor (first)
import Kroha.Parser.Statements (body, statement)
import Control.Monad (void)

globalVariable w f = f <$> (w *> name) <*> typeSpecification <*> (symbol "=" *> literal)

Expand All @@ -32,7 +33,9 @@ globals = recover (choice (fmap krP [constant, variable, manualDeclarations, fra
skip = do someTill (satisfy (const True)) (const' <|> var' <|> manual' <|> frame')
return (ManualFrame "" "'")

program = krP $ Program <$> (program' *> braces (many globals))
program = krP $ Program <$> prog (many globals) <* endOfFile
where prog p = (program' *> (braces p <|> symbol ";" *> p)) <|> p
endOfFile = eof <|> void (symbol "=======" *> lexeme (some (noneOf "=") <* symbol "=======")) <?> "end of file"

parseProgram :: String -> String -> Either String (Program (SourcePos, SourcePos))
parseProgram name = first errorBundlePretty . runParser program name
5 changes: 4 additions & 1 deletion src/Kroha/Parser/Lexer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,13 +36,16 @@ krP p = do
around l r = between (symbol l) (symbol r)

parens = around "(" ")"
angles = around "<" ">"
braces = around "{" "}"
parensOpt p = parens p <|> p


name, name' :: Parser String
name' = (:) <$> letterChar <*> many (alphaNumChar <|> char '_')
name = lexeme (name' <?> "identifier")

callName = around "<" ">" name <|> name

literal = IntegerLiteral <$> nat <?> "integer literal"
lvalue = (VariableLVal <$> name <?> "variable name") <|> (RegisterLVal <$> lexeme (char '%' *> name') <?> "register name")
rvalue = (RLiteral <$> literal) <|> (AsRValue <$> lvalue)
Expand Down
6 changes: 3 additions & 3 deletions src/Kroha/Parser/Statements.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,9 +8,9 @@ import Text.Megaparsec
import Data.Tuple.Extra (curry3)
import Text.Megaparsec.Char (space1)

break = krP $ Break <$> (break' *> parens name)
break = krP $ Break <$> (break' *> parensOpt name)
inline = krP (Inline <$> (symbol "!" *> many (noneOf "\n"))) <* space1
call = krP $ Call <$> (call' *> angles name) <*> parens (rvalue `sepBy` symbol ",")
call = krP $ Call <$> (call' *> callName) <*> parens (rvalue `sepBy` symbol ",")

register = krP $ VariableDeclaration <$> (RegisterVariable <$> (reg' *> name) <*> (symbol ":" *> (name <?> "register name")))
variable = krP $ VariableDeclaration <$> (StackVariable <$> (var' *> name) <*> typeSpecification)
Expand All @@ -30,7 +30,7 @@ ifStatement pStatement = krP $
p x s = x <$ symbol s
cmpToken = p Equals "==" <|> p NotEquals "!=" <|> p Greater ">" <|> p Less "<"

loop ps = krP $ Loop <$> (loop' *> parens name) <*> body' ps
loop ps = krP $ Loop <$> (loop' *> parensOpt name) <*> body' ps

statement = recover (choice ( fmap (<* end)
[ inline, call, Kroha.Parser.Statements.break,
Expand Down
1 change: 1 addition & 0 deletions test/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ cases =
, "examples/nestedIfs"
, "examples/loops"
, "examples/semicolons"
, "examples/elseif"

, "errors/scopeErrors"
, "errors/typeErrors" ]
Expand Down
35 changes: 35 additions & 0 deletions test/examples/elseif.test.kr
Original file line number Diff line number Diff line change
@@ -0,0 +1,35 @@
program {
frame sign {
reg x : bx

if (x > 0, XGTZ) {
x = 2
}
else if (x == 0, XEZ) {
x = 1
}
else {
x = 0
}
!dec bx
}
}
======= nasm =======
section .text
sign:
cmp bx, 0
jg XGTZ_begin
cmp bx, 0
je XEZ_begin
mov bx, 0
jmp XEZ_end
XEZ_begin:
mov bx, 1
XEZ_end:
jmp XGTZ_end
XGTZ_begin:
mov bx, 2
XGTZ_end:
dec bx
leave
ret
29 changes: 13 additions & 16 deletions test/examples/frameVariables.test.kr
Original file line number Diff line number Diff line change
@@ -1,21 +1,19 @@
program {
frame register {
reg x : ax
reg y : bx
frame register {
reg x : ax
reg y : bx

x = 5
y = x
}
x = 5
y = x
}

frame stackNreg {
var x : int16
reg y : ax
frame stackNreg {
var x : int16
reg y : ax

x = 5
y = x
x = y
y = 6
}
x = 5
y = x
x = y
y = 6
}

======= nasm =======
Expand All @@ -34,4 +32,3 @@ stackNreg:
mov ax, 6
leave
ret

6 changes: 4 additions & 2 deletions test/examples/functionCall.test.kr
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,8 @@ program {
}

frame callFunction {
call <justFunc>()
call<justFunc>()
call justFunc()
!nop
}
}
Expand All @@ -18,9 +19,10 @@ ret

section .text
callFunction:
call justFunc
add sp, 0
call justFunc
add sp, 0
nop
leave
ret

14 changes: 5 additions & 9 deletions test/examples/functionDeclaration.test.kr
Original file line number Diff line number Diff line change
@@ -1,11 +1,9 @@
program {
frame start {
!nop
}
frame start {
!nop
}

manual frame mf {
add ax, dx
}
manual frame mf {
add ax, dx
}

======= nasm =======
Expand All @@ -18,5 +16,3 @@ ret
section .text
mf:
add ax, dx


38 changes: 17 additions & 21 deletions test/examples/if.test.kr
Original file line number Diff line number Diff line change
@@ -1,27 +1,24 @@
program {
frame if_eq {
reg x : ax

if (x == 5, A) {
!inc ax
}

!nop
frame if_eq {
reg x : ax

if (x == 5, A) {
!inc ax
}

frame if_comp {
reg x : ax

if (x > 5, B) {
!add ax, 5
}
!nop
}

if (x < 7, C) {
!sub ax, 7
}
frame if_comp {
reg x : ax

!nop
if (x > 5, B) {
!add ax, 5
}

if (x < 7, C)
!sub ax, 7

!nop
}

======= nasm =======
Expand Down Expand Up @@ -49,9 +46,8 @@ if_comp:
jl C_begin
jmp C_end
C_begin:
sub ax, 7
sub ax, 7
C_end:
nop
leave
ret

45 changes: 20 additions & 25 deletions test/examples/ifelse.test.kr
Original file line number Diff line number Diff line change
@@ -1,29 +1,25 @@
program {
frame ifelse_eq {
reg x : ax

if (x == 5, A) {
!dec ax
}
else {
!inc ax
}

!nop
frame ifelse_eq {
reg x : ax

if (x == 5, A) {
!dec ax
}
else {
!inc ax
}

frame ifelse_comp {
reg x : ax
!nop
}

if (x < 5, B) {
!dec ax
}
else {
!inc ax
}
frame ifelse_comp {
reg x : ax

!nop
}
if (x < 5, B)
!dec ax
else
!inc ax

!nop
}

======= nasm =======
Expand All @@ -44,12 +40,11 @@ section .text
ifelse_comp:
cmp ax, 5
jl B_begin
inc ax
inc ax
jmp B_end
B_begin:
dec ax
dec ax
B_end:
nop
leave
ret

42 changes: 28 additions & 14 deletions test/examples/loops.test.kr
Original file line number Diff line number Diff line change
@@ -1,23 +1,29 @@
program {
frame infLoop {
loop (IL) {
!inc ax
}
frame infLoop {
loop (IL) {
!inc ax
}

frame main {
reg x : ax
loop IL2
!inc ax
}

frame main {
reg x : ax

loop (JL) {
!inc ax
loop JL {
!inc ax

if (x > 5, BL) {
break (JL)
}
if (x > 5, BL) {
break (JL)
}
}

!nop
loop PL {
!xor ax, ax
break PL
}

!nop
}

======= nasm =======
Expand All @@ -27,6 +33,10 @@ infLoop:
inc ax
jmp IL_begin
IL_end:
IL2_begin:
inc ax
jmp IL2_begin
IL2_end:
leave
ret

Expand All @@ -42,7 +52,11 @@ main:
BL_end:
jmp JL_begin
JL_end:
PL_begin:
xor ax, ax
jmp PL_end
jmp PL_begin
PL_end:
nop
leave
ret

Loading

0 comments on commit f3324af

Please sign in to comment.