Skip to content

Commit

Permalink
add better error handler
Browse files Browse the repository at this point in the history
  • Loading branch information
TTENSHII committed Jan 6, 2024
1 parent 2a5ce20 commit d4891b0
Show file tree
Hide file tree
Showing 7 changed files with 101 additions and 44 deletions.
21 changes: 14 additions & 7 deletions lvtrun/app/Errors.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,16 +4,23 @@
-- File description:
-- Errors
-}

module Errors
(
exitWithError
CustomException(..),
handleException
)
where

import System.Exit (exitWith, ExitCode(..))
import Control.Exception (Exception(..), SomeException, displayException)

data CustomException =
ParseError String |
WasmError String |
RuntimeError String
deriving (Show, Eq)

instance Exception CustomException

exitWithError :: String -> IO a
exitWithError msg = do
putStrLn msg
exitWith $ ExitFailure 84
handleException :: SomeException -> IO ()
handleException e = putStrLn $ "Error: " ++ displayException e
10 changes: 7 additions & 3 deletions lvtrun/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,11 +5,15 @@
-- Main
-}


module Main (main) where

import Control.Exception (try)
import WasmMod.Module
import Errors

main :: IO ()
main = do
wasmMod <- loadModule "./test/test.wasm"
print wasmMod
main = try (loadModule "./test/test.wasm") >>= \result ->
case result of
Left err -> handleException err
Right wasmMod -> print wasmMod
10 changes: 7 additions & 3 deletions lvtrun/app/WasmMod/Module.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,12 +13,14 @@ module WasmMod.Module
where

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

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

data WasmModule = WasmModule {
header :: ModHeader,
Expand All @@ -40,7 +42,9 @@ loadModule :: String -> IO WasmModule
loadModule filePath = do
bytes <- getFileContent filePath
let modHeader = getModHeader bytes
when (not $ isHeaderValid modHeader) $ exitWithError "Invalid header"
when (not $ isHeaderValid modHeader) $ throwIO (WasmError "Invalid header")
let modSections = getModSections bytes
when (not $ areSectionsValid modSections) $ exitWithError "Invalid sections"
when (not $ areSectionsValid modSections) $ throwIO (WasmError "Invalid sections")
let funcType = parseTypes $ head modSections
print funcType
return $ WasmModule modHeader modSections
60 changes: 29 additions & 31 deletions lvtrun/app/WasmMod/Sections.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,29 +15,26 @@ module WasmMod.Sections
where

import qualified Data.ByteString.Lazy as BS (ByteString, head, drop, take, null, unpack)
import Data.Binary.Get
import Data.Bits
import Data.Int (Int32, Int64)
import Data.Word (Word8)
import Numeric (showHex)
import WasmMod.Leb128
import Data.Word
import WasmMod.Leb128
import Data.Bits

data SectionID =
Custom
| Type
| Import
| Function
| Table
| Memory
| Global
| Export
| Start
| Element
| Code
| Data
| DataCount
| Invalid
| TypeID
| ImportID
| FunctionID
| TableID
| MemoryID
| GlobalID
| ExportID
| StartID
| ElementID
| CodeID
| DataID
| DataCountID
| InvalidID
deriving (Show, Eq)

data Section = Section {
Expand All @@ -56,19 +53,19 @@ areSectionsValid :: [Section] -> Bool
areSectionsValid sections = True

getSectionID :: Word8 -> SectionID
getSectionID 1 = Type
getSectionID 2 = Import
getSectionID 3 = Function
getSectionID 4 = Table
getSectionID 5 = Memory
getSectionID 6 = Global
getSectionID 7 = Export
getSectionID 8 = Start
getSectionID 9 = Element
getSectionID 10 = Code
getSectionID 11 = Data
getSectionID 12 = DataCount
getSectionID _ = Invalid
getSectionID 1 = TypeID
getSectionID 2 = ImportID
getSectionID 3 = FunctionID
getSectionID 4 = TableID
getSectionID 5 = MemoryID
getSectionID 6 = GlobalID
getSectionID 7 = ExportID
getSectionID 8 = StartID
getSectionID 9 = ElementID
getSectionID 10 = CodeID
getSectionID 11 = DataID
getSectionID 12 = DataCountID
getSectionID _ = InvalidID

getSection :: BS.ByteString -> (Section, BS.ByteString)
getSection bytes = do
Expand All @@ -90,5 +87,6 @@ getModSections' = do
in section : getModSections'' rest
getModSections''

-- Todo: Check if sections are valid
getModSections :: BS.ByteString -> [Section]
getModSections bytes = getModSections' (removeHeader bytes)
43 changes: 43 additions & 0 deletions lvtrun/app/WasmMod/Sections/Types.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,43 @@
{-
-- EPITECH PROJECT, 2023
-- Leviator Run
-- File description:
-- Types
-}

module WasmMod.Sections.Types
(
parseTypes,
Type(..),
FuncType(..)
)
where

import WasmMod.Sections
import WasmMod.Leb128
import Data.Int
import Errors
import Control.Exception
import qualified Data.ByteString.Lazy as Bs

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

data FuncType = FuncType {
typeId :: Int,
params :: [Type],
results :: [Type]
}

instance Show FuncType where
show funcType = "(type " ++ (show $ typeId funcType) ++ " (func " ++
(show $ params funcType) ++ ") " ++ (show $ results funcType) ++ ")"

parseFuncTypes :: Int64 -> Bs.ByteString -> [FuncType]
parseFuncTypes 0 _ = []
parseFuncTypes idx content = throw $ (WasmError "Not implemented")

parseTypes :: Section -> [FuncType]
parseTypes (Section TypeID _ content) = do
let (vecSize, rest) = extractLEB128 content
parseFuncTypes vecSize rest
parseTypes _ = []
1 change: 1 addition & 0 deletions lvtrun/lvtrun.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -47,6 +47,7 @@ executable lvtrun-exe
WasmMod.Leb128
WasmMod.Module
WasmMod.Sections
WasmMod.Sections.Types
Paths_lvtrun
autogen-modules:
Paths_lvtrun
Expand Down
Binary file modified lvtrun/test/HexFile
Binary file not shown.

0 comments on commit d4891b0

Please sign in to comment.