[Git][ghc/ghc][wip/js-staging] 3 commits: JS.Arg: docs and cleanup
doyougnu (@doyougnu)
gitlab at gitlab.haskell.org
Wed Sep 28 13:43:48 UTC 2022
doyougnu pushed to branch wip/js-staging at Glasgow Haskell Compiler / GHC
Commits:
5340102e by doyougnu at 2022-09-28T09:43:09-04:00
JS.Arg: docs and cleanup
- - - - -
0332c416 by doyougnu at 2022-09-28T09:43:09-04:00
StgToJS.Arg: add minimal docs
- - - - -
720646df by doyougnu at 2022-09-28T09:43:09-04:00
StgToJS.Ids: Add header
- - - - -
2 changed files:
- compiler/GHC/StgToJS/Arg.hs
- compiler/GHC/StgToJS/Ids.hs
Changes:
=====================================
compiler/GHC/StgToJS/Arg.hs
=====================================
@@ -1,6 +1,20 @@
{-# LANGUAGE LambdaCase #-}
--- | Code generation of application arguments
+-----------------------------------------------------------------------------
+-- |
+-- Module : GHC.StgToJS.Args
+-- Copyright : (c) The University of Glasgow 2001
+-- License : BSD-style (see the file LICENSE)
+--
+-- Maintainer : Jeffrey Young <jeffrey.young at iohk.io>
+-- Luite Stegeman <luite.stegeman at iohk.io>
+-- Sylvain Henry <sylvain.henry at iohk.io>
+-- Josh Meredith <josh.meredith at iohk.io>
+-- Stability : experimental
+--
+-- Code generation of application arguments
+-----------------------------------------------------------------------------
+
module GHC.StgToJS.Arg
( genArg
, genIdArg
@@ -94,6 +108,7 @@ JavaScript runtime.
-}
+-- | Generate JS code for static arguments
genStaticArg :: HasDebugCallStack => StgArg -> G [StaticArg]
genStaticArg a = case a of
StgLitArg l -> map StaticLitArg <$> genStaticLit l
@@ -161,9 +176,11 @@ genArg a = case a of
return [allocDynamicE inl_alloc e as Nothing]
x -> pprPanic "genArg: unexpected unfloated expression" (pprStgExpr panicStgPprOpts x)
+-- | Generate a Var as JExpr
genIdArg :: HasDebugCallStack => Id -> G [JExpr]
genIdArg i = genArg (StgVarArg i)
+-- | Generate an Id as an Ident
genIdArgI :: HasDebugCallStack => Id -> G [Ident]
genIdArgI i
| isVoid r = return []
@@ -172,14 +189,14 @@ genIdArgI i
where
r = uTypeVt . idType $ i
-
+-- | Generate IDs for stack arguments. See 'StgToJS.Expr.loadRetArgs' for use case
genIdStackArgI :: HasDebugCallStack => Id -> G [(Ident,StackSlot)]
genIdStackArgI i = zipWith f [1..] <$> genIdArgI i
where
f :: Int -> Ident -> (Ident,StackSlot)
f n ident = (ident, SlotId i n)
-
+-- | Allocate Static Constructors
allocConStatic :: HasDebugCallStack => Ident -> CostCentreStack -> DataCon -> [StgArg] -> G ()
allocConStatic (TxtI to) cc con args = do
as <- mapM genStaticArg args
@@ -217,6 +234,7 @@ allocConStatic (TxtI to) cc con args = do
(TxtI e) <- identForDataConWorker con
emitStatic to (StaticData e xs) cc'
+-- | Allocate unboxed constructors
allocUnboxedConStatic :: DataCon -> [StaticArg] -> StaticArg
allocUnboxedConStatic con = \case
[]
@@ -229,6 +247,7 @@ allocUnboxedConStatic con = \case
_ -> pprPanic "allocUnboxedConStatic: not an unboxed constructor" (ppr con)
+-- | Allocate Static list
allocateStaticList :: [StgArg] -> StgArg -> G StaticVal
allocateStaticList xs a@(StgVarArg i)
| isDataConId_maybe i == Just nilDataCon = listAlloc xs Nothing
=====================================
compiler/GHC/StgToJS/Ids.hs
=====================================
@@ -1,4 +1,18 @@
--- | Deals with JS identifiers
+-----------------------------------------------------------------------------
+-- |
+-- Module : GHC.StgToJS.Ids
+-- Copyright : (c) The University of Glasgow 2001
+-- License : BSD-style (see the file LICENSE)
+--
+-- Maintainer : Jeffrey Young <jeffrey.young at iohk.io>
+-- Luite Stegeman <luite.stegeman at iohk.io>
+-- Sylvain Henry <sylvain.henry at iohk.io>
+-- Josh Meredith <josh.meredith at iohk.io>
+-- Stability : experimental
+--
+-- Module to deal with JS identifiers
+-----------------------------------------------------------------------------
+
module GHC.StgToJS.Ids
( freshUnique
, freshIdent
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/028fb846a33c96a1d4880d52cc7f2f8892a5006a...720646df58af0b44787fa32efda584d3d2b279bb
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/028fb846a33c96a1d4880d52cc7f2f8892a5006a...720646df58af0b44787fa32efda584d3d2b279bb
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/20220928/f3253ed3/attachment-0001.html>
More information about the ghc-commits
mailing list