Skip to content

Commit

Permalink
add type parsing
Browse files Browse the repository at this point in the history
  • Loading branch information
TTENSHII committed Jan 7, 2024
1 parent f848b1e commit 7623136
Show file tree
Hide file tree
Showing 7 changed files with 126 additions and 21 deletions.
22 changes: 12 additions & 10 deletions lvtrun/README.md
Original file line number Diff line number Diff line change
Expand Up @@ -48,8 +48,8 @@
# ----------------------- 3 -----------------------

# section 3 is the function section with 17 bytes of length
03 11
10 01 00 01
03 11 10
01 00 01
01 01 02 02
00 01 00 00
00 00 02 03 00
Expand Down Expand Up @@ -80,14 +80,16 @@

# ----------------------- 6 ----------------------- the global section

06
12

03 7f 01
41 c7 c7 04
0b 7f 01 41
00 0b 7f 01
41 00 0b
06 12
# vector of 3 globals
03
# i32 mut = i32.const 66560
7f 01 41 c7 c7 04 0b
7f 01 41 00 0b
7f 01 41 00 0b
# (globalType, expr)
# globalType = (valtype, mut) with mut 0x00 = const, 0x01 = var
# expr = (instructions) 0xb

# ----------------------- 7 -----------------------

Expand Down
27 changes: 27 additions & 0 deletions lvtrun/app/Types.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,27 @@
{-
-- EPITECH PROJECT, 2023
-- Leviator Run
-- File description:
-- Types
-}

module Types
(
Type(..),
getTypeFromByte
)
where

import Data.Word (Word8)
import Control.Exception (throw)

import Errors

data Type = I32 | I64 | F32 | F64 deriving (Show, Eq)

getTypeFromByte :: Word8 -> Type
getTypeFromByte 0x7f = I32
getTypeFromByte 0x7e = I64
getTypeFromByte 0x7d = F32
getTypeFromByte 0x7c = F64
getTypeFromByte _ = throw $ WasmError "GetTypeFromByte: bad type"
12 changes: 11 additions & 1 deletion lvtrun/app/WasmMod/Module.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,14 +13,15 @@ module WasmMod.Module
where

import qualified Data.ByteString.Lazy as BS (ByteString, unpack, readFile)
import Control.Exception (throwIO)
import Control.Exception (throwIO, throw)
import Control.Monad (when)
import Numeric (showHex)

import Errors
import WasmMod.Header
import WasmMod.Sections
import WasmMod.Sections.Types
import WasmMod.Sections.Global

data WasmModule = WasmModule {
header :: ModHeader,
Expand All @@ -38,6 +39,13 @@ instance Show WasmModule where
getFileContent :: String -> IO BS.ByteString
getFileContent path = BS.readFile path

--TEMP FUNC
getGlobalSection :: [Section] -> Section
getGlobalSection [] = throw (WasmError "No global section")
getGlobalSection (x:xs)
| identifier x == GlobalID = x
| otherwise = getGlobalSection xs

loadModule :: String -> IO WasmModule
loadModule filePath = do
bytes <- getFileContent filePath
Expand All @@ -47,4 +55,6 @@ loadModule filePath = do
when (not $ areSectionsValid modSections) $ throwIO (WasmError "Invalid sections")
let funcType = parseTypes $ head modSections
print funcType
let globals = parseGlobals $ getGlobalSection modSections
print globals
return $ WasmModule modHeader modSections
72 changes: 72 additions & 0 deletions lvtrun/app/WasmMod/Sections/Global.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,72 @@
{-
-- EPITECH PROJECT, 2023
-- Leviator Run
-- File description:
-- Global
-}

module WasmMod.Sections.Global
(
parseGlobals,
Global(..)
)
where

import qualified Data.ByteString.Lazy as Bs
import Control.Exception (throw)
import Data.Word (Word8)
import Data.Int (Int64)

import WasmMod.Leb128
import WasmMod.Sections (Section(..), SectionID(..))
import Types (Type(..), getTypeFromByte)
import Errors

data Mutability = Const | Var deriving (Show)

data Global = Global {
globalType :: Type,
mutability :: Mutability,
initExp :: [Word8]
}

instance Show Global where
show global = "Global: " ++ (show $ globalType global) ++ " " ++
(show $ mutability global) ++ " " ++ (show $ initExp global) ++ "\n"

parseMutability :: Word8 -> Mutability
parseMutability 0x00 = Const
parseMutability 0x01 = Var
parseMutability _ = throw $ WasmError "ParseMutability: bad mutability"

getHexaIndex :: Bs.ByteString -> Int64 -> Int64
getHexaIndex content idx
| idx >= (fromIntegral $ Bs.length content) = throw $ WasmError "GetHexaIndex: no 0x0b found"
| (head $ Bs.unpack $ Bs.drop (fromIntegral idx) content) == 0x0b = idx
| otherwise = getHexaIndex content (idx + 1)

extractExpression :: Bs.ByteString -> ([Word8], Bs.ByteString)
extractExpression content = do
let idx = getHexaIndex content 0
let expression = Bs.take (fromIntegral (idx + 1)) content
(Bs.unpack expression, Bs.drop (fromIntegral (idx + 1)) content)

parseGlobal :: Bs.ByteString -> (Global, Bs.ByteString)
parseGlobal content = do
let globalType = getTypeFromByte (head $ Bs.unpack content)
let mutability = parseMutability (head $ Bs.unpack $ Bs.drop 1 content)
let (expression, rest) = extractExpression (Bs.drop 2 content)
(Global globalType mutability expression, rest)

parseGlobals' :: Int64 -> Int64 -> Bs.ByteString -> [Global]
parseGlobals' idx maxIdx content
| idx >= maxIdx = []
| otherwise = do
let (global, rest) = parseGlobal content
global : parseGlobals' (idx + 1) maxIdx rest

parseGlobals :: Section -> [Global]
parseGlobals (Section GlobalID _ content) = do
let (vecSize, rest) = extractLEB128 content
parseGlobals' 0 vecSize rest
parseGlobals _ = throw $ WasmError "ParseGlobals: bad section"
12 changes: 2 additions & 10 deletions lvtrun/app/WasmMod/Sections/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,8 +21,7 @@ import Data.Word (Word8)
import WasmMod.Sections
import WasmMod.Leb128
import Errors

data Type = I32 | I64 | F32 | F64 deriving (Show, Eq)
import Types (Type(..), getTypeFromByte)

data FuncType = FuncType {
typeId :: Int,
Expand All @@ -37,13 +36,6 @@ instance Show FuncType where
getVectorSize :: Bs.ByteString -> (Int64, Bs.ByteString)
getVectorSize content = extractLEB128 content

getTypeFromByte :: Word8 -> Type
getTypeFromByte 0x7f = I32
getTypeFromByte 0x7e = I64
getTypeFromByte 0x7d = F32
getTypeFromByte 0x7c = F64
getTypeFromByte _ = throw $ WasmError "GetTypeFromByte: bad type"

extractTypes :: (Int64, Bs.ByteString) -> ([Type], Bs.ByteString)
extractTypes (0, content) = ([], content)
extractTypes (idx, content) = (getTypeFromByte (head $ Bs.unpack content) : types, rest)
Expand All @@ -67,4 +59,4 @@ parseTypes :: Section -> [FuncType]
parseTypes (Section TypeID _ content) = do
let (vecSize, rest) = extractLEB128 content
parseFuncTypes 0 vecSize rest
parseTypes _ = []
parseTypes _ = throw $ WasmError "ParseTypes: bad section"
2 changes: 2 additions & 0 deletions lvtrun/lvtrun.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -43,10 +43,12 @@ executable lvtrun-exe
main-is: Main.hs
other-modules:
Errors
Types
WasmMod.Header
WasmMod.Leb128
WasmMod.Module
WasmMod.Sections
WasmMod.Sections.Global
WasmMod.Sections.Types
Paths_lvtrun
autogen-modules:
Expand Down
Binary file modified lvtrun/test/HexFile
Binary file not shown.

0 comments on commit 7623136

Please sign in to comment.