Skip to content

Commit

Permalink
Merge pull request #15 from X-R-G-B/step-7th-wasm
Browse files Browse the repository at this point in the history
Step 7th wasm
  • Loading branch information
Saverio976 authored Jan 13, 2024
2 parents fe30d5f + 4f91529 commit 33ef5e8
Show file tree
Hide file tree
Showing 16 changed files with 822 additions and 128 deletions.
1 change: 0 additions & 1 deletion lvtc/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,6 @@ dispatchArgs :: Args -> IO ()
dispatchArgs (Args Run fPath oFile) = run (Args Run fPath oFile)
dispatchArgs (Args ShowHelp _ _) = printHelp
dispatchArgs (Args ShowVersion _ _) = printVersion
-- dispatchArgs (Args New _ _) =

dispatchIfOk :: Either Args String -> IO ()
dispatchIfOk (Left args) = dispatchArgs args
Expand Down
4 changes: 4 additions & 0 deletions lvtc/lvtc.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -35,9 +35,12 @@ library
Parser
ParseUtil
ShuntingYard
Wasm
WasmUtils
WatAST
WatLike
WatLikeToWat
WatToWasm
other-modules:
Paths_lvtc
autogen-modules:
Expand Down Expand Up @@ -74,6 +77,7 @@ test-suite lvtc-test
other-modules:
UTParseLvt
UTShuntingYard
UTWasm
UTWat
UTWatLike
Paths_lvtc
Expand Down
5 changes: 4 additions & 1 deletion lvtc/src/AST.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@ module AST
, VarAssignation
, Condition
, Symbol
, IsFuncExport
) where

import Data.Int (Int32)
Expand Down Expand Up @@ -57,7 +58,9 @@ instance Eq Value where

type Var = (Symbol, Type)

type FuncPrototype = (Symbol, [Var], Type)
type IsFuncExport = Bool

type FuncPrototype = (IsFuncExport, Symbol, [Var], Type)

type FuncDeclaration = (FuncPrototype, [Instruction])

Expand Down
42 changes: 21 additions & 21 deletions lvtc/src/Builtins.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,21 +21,21 @@ import WatAST
getBuiltinsFuncOperator :: [FuncDeclaration]
getBuiltinsFuncOperator =
[
(("+", [("x", "Int"), ("y", "Int")], "Int"), []),
(("-", [("x", "Int"), ("y", "Int")], "Int"), []),
(("*", [("x", "Int"), ("y", "Int")], "Int"), []),
(("/", [("x", "Int"), ("y", "Int")], "Int"), [])
((False, "+", [("x", "Int"), ("y", "Int")], "Int"), []),
((False, "-", [("x", "Int"), ("y", "Int")], "Int"), []),
((False, "*", [("x", "Int"), ("y", "Int")], "Int"), []),
((False, "/", [("x", "Int"), ("y", "Int")], "Int"), [])
]

getBuiltinsFuncComp :: [FuncDeclaration]
getBuiltinsFuncComp =
[
(("==", [("x", "Int"), ("y", "Int")], "Int"), []),
(("<", [("x", "Int"), ("y", "Int")], "Int"), []),
((">", [("x", "Int"), ("y", "Int")], "Int"), []),
(("<=", [("x", "Int"), ("y", "Int")], "Int"), []),
((">=", [("x", "Int"), ("y", "Int")], "Int"), []),
(("!=", [("x", "Int"), ("y", "Int")], "Int"), [])
((False, "==", [("x", "Int"), ("y", "Int")], "Int"), []),
((False, "<", [("x", "Int"), ("y", "Int")], "Int"), []),
((False, ">", [("x", "Int"), ("y", "Int")], "Int"), []),
((False, "<=", [("x", "Int"), ("y", "Int")], "Int"), []),
((False, ">=", [("x", "Int"), ("y", "Int")], "Int"), []),
((False, "!=", [("x", "Int"), ("y", "Int")], "Int"), [])
]

getBuiltinsFunc :: [FuncDeclaration]
Expand All @@ -47,28 +47,28 @@ getStackRet op = [LocalGet 0, LocalGet 1] ++ op ++ [WatAST.Return]
getBuiltinsWatOperator :: [FuncDef]
getBuiltinsWatOperator =
[
FuncDef 0 [I32, I32] I32 (getStackRet [I32Add]) [],
FuncDef 1 [I32, I32] I32 (getStackRet [I32Sub]) [],
FuncDef 2 [I32, I32] I32 (getStackRet [I32Mul]) [],
FuncDef 3 [I32, I32] I32 (getStackRet [I32Div]) []
FuncDef False "+" 0 [I32, I32] I32 (getStackRet [I32Add]) [],
FuncDef False "-" 1 [I32, I32] I32 (getStackRet [I32Sub]) [],
FuncDef False "*" 2 [I32, I32] I32 (getStackRet [I32Mul]) [],
FuncDef False "/" 3 [I32, I32] I32 (getStackRet [I32Div]) []
]

getBuiltinsWatComp :: [FuncDef]
getBuiltinsWatComp = [
FuncDef 4 [I32, I32] I32 (getStackRet [I32EQ]) [],
FuncDef 5 [I32, I32] I32 (getStackRet [I32LT_S]) [],
FuncDef 6 [I32, I32] I32 (getStackRet [I32GT_S]) [],
FuncDef 7 [I32, I32] I32 (getStackRet [I32LE_S]) [],
FuncDef 8 [I32, I32] I32 (getStackRet [I32GE_S]) [],
FuncDef 9 [I32, I32] I32 (getStackRet [I32NE]) []
FuncDef False "==" 4 [I32, I32] I32 (getStackRet [I32EQ]) [],
FuncDef False "<" 5 [I32, I32] I32 (getStackRet [I32LT_S]) [],
FuncDef False ">" 6 [I32, I32] I32 (getStackRet [I32GT_S]) [],
FuncDef False "<=" 7 [I32, I32] I32 (getStackRet [I32LE_S]) [],
FuncDef False ">=" 8 [I32, I32] I32 (getStackRet [I32GE_S]) [],
FuncDef False "!=" 9 [I32, I32] I32 (getStackRet [I32NE]) []
]

getBuiltinsWat :: [FuncDef]
getBuiltinsWat = getBuiltinsWatOperator ++ getBuiltinsWatComp

isBuiltinsFuncString :: String -> [FuncDeclaration] -> Bool
isBuiltinsFuncString _ [] = False
isBuiltinsFuncString name (((name', _, _), _):xs)
isBuiltinsFuncString name (((_, name', _, _), _):xs)
| name == name' = True
| otherwise = isBuiltinsFuncString name xs

Expand Down
39 changes: 17 additions & 22 deletions lvtc/src/ParseLvt.hs
Original file line number Diff line number Diff line change
Expand Up @@ -91,17 +91,16 @@ parseStringView =
*> parseAllCharUntil "\""
)

parseVar :: Parser Value
parseVar = Parser f
parseVarName :: Parser Symbol
parseVarName =
f
<$> parseAnyChar alphabetLower
<*> many (parseAnyChar (alphabet ++ digit ++ "_"))
where
f str = case runParser (parseAnyChar alphabetLower) str of
Nothing -> Nothing
Just (x, xs) ->
case runParser
(many (parseAnyChar (alphabet ++ digit ++ "_"))) xs
of
Nothing -> Nothing
Just (y, ys) -> Just (Var (x:y), ys)
f fstChar restName = fstChar : restName

parseVar :: Parser Value
parseVar = Var <$> parseVarName

parseVoid :: Parser Value
parseVoid = f <$> parseString "Void"
Expand Down Expand Up @@ -233,7 +232,7 @@ parseFunction :: Parser Instruction
parseFunction = parseCall

parseReturn :: Parser Instruction
parseReturn = Return <$> ((parseString "<-") *> parseValue)
parseReturn = Return <$> (parseString "<-" *> parseValue)

parseType :: Parser String
parseType =
Expand Down Expand Up @@ -331,16 +330,10 @@ parseFuncVars =
<|> parseFuncVar)
<* parseChar ')'

parseFuncName :: Parser Symbol
parseFuncName = Parser f
where
f str = case runParser
((parseString "export fn " <|> parseString "fn ") *> parseVar)
str
of
Nothing -> Nothing
Just (Var x, xs) -> Just (x, xs)
_notVar -> Nothing
parseFuncName :: Parser (IsFuncExport, Symbol)
parseFuncName =
((\x -> (True, x)) <$> (parseString "export fn " *> parseVarName))
<|> ((\x -> (False, x)) <$> (parseString "fn " *> parseVarName))

parseFuncType :: Parser Type
parseFuncType =
Expand All @@ -350,10 +343,12 @@ parseFuncType =

parseFuncPrototype :: Parser FuncPrototype
parseFuncPrototype =
(,,)
f
<$> parseFuncName
<*> parseFuncVars
<*> parseFuncType
where
f (isExport, name) vars funcType = (isExport, name, vars, funcType)

parseFuncDeclaration' :: Parser FuncDeclaration
parseFuncDeclaration' =
Expand Down
125 changes: 125 additions & 0 deletions lvtc/src/Wasm.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,125 @@
{-
-- EPITECH PROJECT, 2023
-- Leviator compiler
-- File description:
-- ShuntingYard
-}

module Wasm
(
VariableType (..)
, TypeSectionType (..)
, TypeSection (..)
, FunctionSection (..)
, MemorySection (..)
, ExportSectionExportType (..)
, ExportSectionExport (..)
, ExportSection (..)
, CodeSectionCodeLocals
, CodeSectionCode (..)
, CodeSection (..)
, Wasm (..)
) where

import WatAST (OpCode (..))
import Data.Int (Int32)

data VariableType =
I32
deriving (Show, Eq)

data TypeSectionType =
Func {
headerFunc :: Int,
nbParams :: Int,
params :: [VariableType],
nbResults :: Int,
results :: [VariableType]
}
deriving (Show, Eq)

data TypeSection =
TS {
headerTS :: Int,
sizeTS :: Int,
nbTypes :: Int,
types :: [TypeSectionType]
}
deriving (Show, Eq)

data FunctionSection =
FS {
headerFS :: Int,
sizeFS :: Int,
nbFuncs :: Int,
funcs :: [Int]
}
deriving (Show, Eq)

data MemorySection =
MS {
headerMS :: Int,
sizeMS :: Int,
hasMax :: Int,
minMS :: Int,
maxMS :: Int
}
deriving (Show, Eq)

data ExportSectionExportType =
FuncExport
| TableExport
| MemoryExport
| GlobalExport
deriving (Show, Eq)

data ExportSectionExport =
ESE {
nameLength :: Int,
name :: String,
typeESE :: ExportSectionExportType,
indexESE :: Int
}
deriving (Show, Eq)

data ExportSection =
ES {
headerES :: Int,
sizeES :: Int,
nbExports :: Int,
exports :: [ExportSectionExport]
}
deriving (Show, Eq)

type CodeSectionCodeLocals = (Int32, VariableType)

data CodeSectionCode =
CSC {
sizeCSC :: Int,
nbLocals :: Int,
locals :: [CodeSectionCodeLocals],
bodyCSC :: [OpCode],
endCSC :: Int
}
deriving (Show, Eq)

data CodeSection =
CS {
headerCS :: Int,
sizeCS :: Int,
nbCodes :: Int,
codes :: [CodeSectionCode]
}
deriving (Show, Eq)

data Wasm =
Wasm {
headerWasm :: (Int, Int, Int, Int),
versionWasm :: (Int, Int, Int, Int),
typeSection :: TypeSection,
functionSection :: FunctionSection,
memorySection :: MemorySection,
exportSection :: ExportSection,
codeSection :: CodeSection
}
deriving (Show, Eq)
Loading

0 comments on commit 33ef5e8

Please sign in to comment.