Skip to content

Commit 0b6cd68

Browse files
committed
Added control flow statement if-then-else
1 parent cc13dbe commit 0b6cd68

File tree

3 files changed

+63
-5
lines changed

3 files changed

+63
-5
lines changed

src/CodeGen.hs

Lines changed: 23 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -28,9 +28,14 @@ module CodeGen (
2828
alloca,
2929
execCodegen,
3030
setBlock,
31+
getBlock,
3132
emptyBlock,
3233
unikName,
33-
entryBlockName
34+
entryBlockName,
35+
br,
36+
phi,
37+
cbr,
38+
fcmp
3439

3540
)where
3641

@@ -47,6 +52,7 @@ import qualified LLVM.AST as ASTL
4752
import qualified LLVM.AST.Constant as C
4853
import qualified LLVM.AST.Float as F
4954
import qualified LLVM.AST.FloatingPointPredicate as FP
55+
import qualified LLVM.AST.IntegerPredicate as IP
5056

5157
import Data.Word
5258
import Data.String
@@ -199,7 +205,8 @@ setBlock bname = do
199205
modify $ \s -> s { currentBlock = bname }
200206
return bname
201207

202-
208+
getBlock :: Codegen ASTL.Name
209+
getBlock = gets currentBlock
203210

204211
-- | Alloca Returns an instruction of declaration of
205212
-- | A var of allocatedType :: Type , numElements , alignment , metadata
@@ -288,4 +295,17 @@ store :: ASTL.Operand -> ASTL.Operand -> Codegen ASTL.Operand
288295
store ptr val = instr $ Store False ptr val Nothing 0 []
289296

290297
load :: ASTL.Operand -> Codegen ASTL.Operand
291-
load ptr = instr $ Load False ptr Nothing 0 []
298+
load ptr = instr $ Load False ptr Nothing 0 []
299+
300+
-- Control Flow
301+
br :: ASTL.Name -> Codegen (ASTL.Named ASTL.Terminator)
302+
br val = terminator $ ASTL.Do $ ASTL.Br val []
303+
304+
cbr :: ASTL.Operand -> ASTL.Name -> ASTL.Name -> Codegen (ASTL.Named ASTL.Terminator)
305+
cbr cond tr fl = terminator $ ASTL.Do $ ASTL.CondBr cond tr fl []
306+
307+
phi :: ASTL.Type -> [(ASTL.Operand, ASTL.Name)] -> Codegen ASTL.Operand
308+
phi ty incoming = instr $ ASTL.Phi ty incoming []
309+
310+
fcmp :: IP.IntegerPredicate -> ASTL.Operand -> ASTL.Operand -> Codegen ASTL.Operand
311+
fcmp cond a b = instr $ ICmp cond a b []

src/Emit.hs

Lines changed: 33 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,7 @@ import qualified LLVM.AST.Float as F
4141
import qualified LLVM.AST.FloatingPointPredicate as FP
4242
import qualified LLVM.AST.CallingConvention as CC
4343
import qualified LLVM.AST.Attribute as A
44-
44+
import qualified LLVM.AST.IntegerPredicate as IP
4545

4646
import Control.Monad.State
4747
import Control.Applicative
@@ -172,6 +172,7 @@ exprGen (FuncCallStmt f) = funcCallGen f
172172
exprGen (LiteralStmt st) = literalGen st
173173
exprGen (BinOpCallStmt st) = binOpCallGen st
174174
exprGen (DeclarationStmt st) = declarationGen st
175+
exprGen (IfthenStmt st) = ifthenGen st
175176

176177
binOpCallGen :: ASTp.BinOpCall -> Codegen ASTL.Operand
177178
binOpCallGen (BinOpCall op lhs rhs) = do
@@ -223,3 +224,34 @@ exprListGen (a:[]) = exprGen a
223224
exprListGen (x:xs) = do
224225
exprGen x
225226
exprListGen xs
227+
228+
ifthenGen :: ASTp.Ifthen -> Codegen ASTL.Operand
229+
ifthenGen (ASTp.Ifthen cond tr fl) = do
230+
ifthen <- addBlock "if.then"
231+
ifelse <- addBlock "if.else"
232+
ifexit <- addBlock "if.exit"
233+
cond <- exprGen cond
234+
test <- fcmp IP.NE zero cond
235+
cbr test ifthen ifelse -- Branch based on the condition
236+
237+
setBlock ifthen
238+
trval <- exprGen tr -- Generate code for the true branch
239+
br ifexit -- Branch to the merge block
240+
ifthen <- getBlock
241+
242+
setBlock ifelse
243+
flval <- exprGen fl -- Generate code for the false branch
244+
br ifexit -- Branch to the merge block
245+
ifelse <- getBlock
246+
247+
setBlock ifexit
248+
phi intL [(trval, ifthen), (flval, ifelse)]
249+
250+
cons :: C.Constant -> Operand
251+
cons = ConstantOperand
252+
253+
one = cons $ C.Int 32 1
254+
zero = cons $ C.Int 32 0
255+
256+
-- def fib(int x):int { if(x) then {fib(x-1)+fib(x-2)} else {1};}
257+
-- def fac(int x):int{ if(x) then { fac(x-1)*x} else {1};}

src/Parser.hs

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
module Parser (
22
moduleParser,
3-
funcParser
3+
funcParser,
4+
ifthenParser
45
)where
56

67
import Lexer
@@ -46,6 +47,7 @@ funcParser = do
4647

4748
exprParser :: Parser Expr
4849
exprParser = try primary
50+
<|> ifthenStmtParser
4951
<|> declarationStmtParser
5052

5153
variableParser :: Parser Expr
@@ -273,6 +275,10 @@ varDeclParser = do
273275
names <- vListParser
274276
return $ VarDecl t names
275277

278+
ifthenStmtParser :: Parser Expr
279+
ifthenStmtParser = do
280+
res <- ifthenParser
281+
return $ IfthenStmt res
276282

277283
ifthenParser :: Parser Ifthen
278284
ifthenParser = do

0 commit comments

Comments
 (0)