Skip to content
Snippets Groups Projects
Commit dd88a260 authored by Luite Stegeman's avatar Luite Stegeman Committed by Marge Bot
Browse files

JS: remove broken newIdents from JStg Monad

GHC.JS.JStg.Monad.newIdents was broken, resulting in duplicate
identifiers being generated in h$c1, h$c2, ... .

This change removes the broken newIdents.
parent 8217acb8
No related branches found
No related tags found
No related merge requests found
......@@ -40,7 +40,6 @@ module GHC.JS.JStg.Monad
, JSM
, withTag
, newIdent
, newIdents
, initJSM
) where
......@@ -95,19 +94,6 @@ newIdent = do env <- get
mk_ident :: FastString -> Unique -> Ident
mk_ident t i = global (mconcat [t, "_", mkFastString (show i)])
-- | A special case optimization over @newIdent@. Given a number of @Ident@ to
-- generate, generate all of them at one time and update the state once rather
-- than n times.
newIdents :: Int -> JSM [Ident]
newIdents 0 = return []
newIdents n = do env <- get
let is = take n (uniqsFromSupply $ ids env)
tag = prefix env
return $ fmap (mk_ident tag) is
-- | Set the tag for @Ident@s for all remaining computations.
tag_names :: FastString -> JSM ()
tag_names tag = modify' (\env -> env {prefix = tag})
......
......@@ -149,6 +149,7 @@ import GHC.JS.JStg.Monad
import GHC.JS.Transform
import Control.Arrow ((***))
import Control.Monad (replicateM)
import Data.Tuple
import qualified Data.Map as M
......@@ -325,7 +326,7 @@ jFunctionSized
-> ([JStgExpr] -> JSM JStgStat) -- ^ function body, input is locally unique generated variables
-> JSM JStgStat
jFunctionSized name arity body = do
func_args <- newIdents arity
func_args <- replicateM arity newIdent
FuncStat name func_args <$> (body $ toJExpr <$> func_args)
-- | Construct a top-level function subject to JS hoisting. Special case where
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment