[Git][ghc/ghc][wip/nr/typed-wasm-control-flow] 2 commits: move code that renders WebAssembly control flow to assembly
Norman Ramsey (@nrnrnr)
gitlab at gitlab.haskell.org
Tue Aug 9 17:01:25 UTC 2022
Norman Ramsey pushed to branch wip/nr/typed-wasm-control-flow at Glasgow Haskell Compiler / GHC
Commits:
44c37f94 by Norman Ramsey at 2022-08-09T13:00:38-04:00
move code that renders WebAssembly control flow to assembly
- - - - -
4c22c583 by Norman Ramsey at 2022-08-09T13:01:01-04:00
make WebAssembly -> .s higher order
- - - - -
2 changed files:
- compiler/GHC/Wasm/Builder.hs → compiler/GHC/Wasm/ControlFlow/ToAsm.hs
- compiler/ghc.cabal.in
Changes:
=====================================
compiler/GHC/Wasm/Builder.hs → compiler/GHC/Wasm/ControlFlow/ToAsm.hs
=====================================
@@ -1,9 +1,10 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
-module GHC.Wasm.Builder
- ( toIndented
- , MyExpr(..), MyActions(..)
+module GHC.Wasm.ControlFlow.ToAsm
+ ( toIndentedAsm
+ , noIndentation
)
where
@@ -21,11 +22,14 @@ import GHC.Utils.Panic
import GHC.Wasm.ControlFlow hiding ((<>))
-defaultIndent :: Builder
+type Indentation = Builder
+
+defaultIndent :: Indentation
defaultIndent = " "
-toIndented :: WasmControl MyActions MyExpr pre post -> Builder
-toIndented s = printWithIndent mempty s <> "\n"
+noIndentation :: Indentation
+noIndentation = ""
+
wasmFunctionType :: WasmFunctionType pre post -> Builder
wasmFunctionType (WasmFunctionType TypeListNil TypeListNil) = ""
@@ -37,41 +41,48 @@ tagBuilder TagI32 = "i32"
tagBuilder TagF32 = "f32"
-printWithIndent :: Builder -> WasmControl MyActions MyExpr pre post -> Builder
-printWithIndent indent s = print s
- where print, outdent :: WasmControl MyActions MyExpr pre post -> Builder
+type Printer a = Indentation -> a -> Builder
+
+-- | Converts WebAssembly control-flow code into GNU (Clang) assembly
+-- syntax, indented for readability. For ease of combining with other
+-- output, the result does not have a trailing newline.
+--
+-- Initial `Indentation` argument gives the indentation of the entire output;
+-- for most use cases it will likely be `mempty`.
+
+toIndentedAsm :: forall s e pre post
+ . Printer s -> Printer e -> Printer (WasmControl s e pre post)
+toIndentedAsm ps pe indent s = print s
+ where print, shift :: WasmControl s e pre' post' -> Builder
newline :: Builder -> Builder -> Builder
(<+>) :: Builder -> Builder -> Builder
ty = wasmFunctionType
+ -- cases meant to avoid generating any output for `WasmFallthrough`
print (WasmFallthrough `WasmSeq` s) = print s
print (s `WasmSeq` WasmFallthrough) = print s
print (WasmIfTop t s WasmFallthrough) =
- "br_if" <+> ty t `newline` outdent s `newline` "end_if"
+ "br_if" <+> ty t `newline` shift s `newline` "end_if"
print (WasmIfTop t WasmFallthrough s) =
- "br_if" <+> ty t `newline` "else" `newline` outdent s `newline` "end_if"
-
- print (WasmPush _ _) = "i32.const 42"
- print (WasmBlock t s) = "block" <+> ty t `newline` outdent s `newline` "end_block"
- print (WasmLoop t s) = "loop" <+> ty t `newline` outdent s `newline` "end_loop"
- print (WasmIfTop t ts fs) = "if" <+> ty t `newline` outdent ts `newline`
- "else" `newline` outdent fs `newline` "end_if"
+ "br_if" <+> ty t `newline` "else" `newline` shift s `newline` "end_if"
+
+ -- normal cases
+ print (WasmPush _ e) = pe indent e
+ print (WasmBlock t s) = "block" <+> ty t `newline` shift s `newline` "end_block"
+ print (WasmLoop t s) = "loop" <+> ty t `newline` shift s `newline` "end_loop"
+ print (WasmIfTop t ts fs) = "if" <+> ty t `newline` shift ts `newline`
+ "else" `newline` shift fs `newline` "end_if"
print (WasmBr l) = "br" <+> BS.intDec l
print (WasmBrTable e _ ts t) =
- myExpr e `newline` "br_table {" <+>
+ pe indent e `newline` "br_table {" <+>
mconcat (intersperse ", " [BS.intDec i | i <- ts <> [t]]) <+>
"}"
print (WasmReturnTop _) = "return"
- print (WasmActions as) = myActions as
+ print (WasmActions as) = ps indent as
print (s `WasmSeq` s') = print s `newline` print s'
print WasmFallthrough = "// fallthrough" -- hopefully rare
newline s s' = s <> "\n" <> indent <> s'
- outdent s = defaultIndent <> printWithIndent (indent <> defaultIndent) s
+ shift s = defaultIndent <> toIndentedAsm ps pe (indent <> defaultIndent) s
s <+> s' = s <> " " <> s'
-
-
-newtype MyExpr = MyExpr { myExpr :: Builder }
-
-newtype MyActions = MyActions { myActions :: Builder }
=====================================
compiler/ghc.cabal.in
=====================================
@@ -805,9 +805,9 @@ Library
GHC.Utils.Ppr.Colour
GHC.Utils.TmpFs
GHC.Utils.Trace
- GHC.Wasm.Builder
GHC.Wasm.ControlFlow
GHC.Wasm.ControlFlow.FromCmm
+ GHC.Wasm.ControlFlow.ToAsm
Language.Haskell.Syntax
Language.Haskell.Syntax.Basic
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c5c029678376197ddd365ba2665c361dd908502d...4c22c583c64f5a15c13080f3aaa5701a6a909c7c
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c5c029678376197ddd365ba2665c361dd908502d...4c22c583c64f5a15c13080f3aaa5701a6a909c7c
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20220809/ee4dc856/attachment-0001.html>
More information about the ghc-commits
mailing list