Skip to content

Commit c0dfe8a

Browse files
committed
Make all bindings global
1 parent 7c7b7b7 commit c0dfe8a

File tree

24 files changed

+139
-111
lines changed

24 files changed

+139
-111
lines changed

lib/Language/PureScript/Backend/IR/Query.hs

+2-1
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,7 @@ import Language.PureScript.Backend.IR.Types
1818
, traverseExpBottomUp
1919
)
2020
import Language.PureScript.Backend.IR.Types qualified as IR
21+
import Language.PureScript.Names (runtimeLazyName)
2122

2223
usesRuntimeLazy UberModule Bool
2324
usesRuntimeLazy UberModule {uberModuleBindings, uberModuleExports} =
@@ -29,7 +30,7 @@ usesRuntimeLazy UberModule {uberModuleBindings, uberModuleExports} =
2930

3031
findRuntimeLazyInExpr Exp Bool
3132
findRuntimeLazyInExpr expr =
32-
countFreeRef (Local (Name "$__runtime_lazy")) expr > 0
33+
countFreeRef (Local (Name runtimeLazyName)) expr > 0
3334

3435
usesPrimModule UberModule Bool
3536
usesPrimModule UberModule {uberModuleBindings, uberModuleExports} =

lib/Language/PureScript/Backend/Lua.hs

+7-8
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE QuasiQuotes #-}
2+
13
module Language.PureScript.Backend.Lua
24
( fromUberModule
35
, fromIR
@@ -68,22 +70,19 @@ fromUberModule foreigns needsRuntimeLazy appOrModule uber = (`evalStateT` 0) do
6870
foreignBindings
6971
forM (Linker.uberModuleForeigns uber) \(IR.QName modname name, irExp) do
7072
exp asExpression <$> fromIR foreigns Set.empty modname irExp
71-
pure (Lua.local1 (fromQName modname name) exp)
73+
pure $ Lua.assign (Lua.VarName (fromQName modname name)) exp
7274
bindings
7375
Linker.uberModuleBindings uber & foldMapM \case
7476
IR.Standalone (IR.QName modname name, irExp) do
7577
exp fromIR foreigns Set.empty modname irExp
76-
pure $
77-
DList.singleton
78-
(Lua.local1 (fromQName modname name) (asExpression exp))
78+
pure . DList.singleton $
79+
Lua.assignVar (fromQName modname name) (asExpression exp)
7980
IR.RecursiveGroup recGroup do
8081
recBinds forM (toList recGroup) \(IR.QName modname name, irExp)
8182
(fromQName modname name,) . asExpression
8283
<$> fromIR foreigns Set.empty modname irExp
8384
let declarations = Lua.local0 . fst <$> DList.fromList recBinds
84-
assignments = DList.fromList do
85-
recBinds <&> \(name, exp)
86-
Lua.assign (Lua.VarName name) exp
85+
assignments = DList.fromList (uncurry Lua.assignVar <$> recBinds)
8786
pure $ declarations <> assignments
8887

8988
returnExp
@@ -282,4 +281,4 @@ uniqueName prefix = do
282281
pure $ Lua.unsafeName (prefix <> show index)
283282

284283
qualifyName ModuleName Lua.Name Lua.Name
285-
qualifyName modname = Name.join2 (fromModuleName modname)
284+
qualifyName modname = Fixture.psluaName . Name.join2 (fromModuleName modname)

lib/Language/PureScript/Backend/Lua/Fixture.hs

+18-6
Original file line numberDiff line numberDiff line change
@@ -3,23 +3,35 @@
33
module Language.PureScript.Backend.Lua.Fixture where
44

55
import Data.String.Interpolate (__i)
6-
import Language.PureScript.Backend.Lua.Name (Name, name)
6+
import Language.PureScript.Backend.Lua.Name (Name, name, unsafeName)
77
import Language.PureScript.Backend.Lua.Name qualified as Name
88
import Language.PureScript.Backend.Lua.Types hiding (var)
99

1010
--------------------------------------------------------------------------------
1111
-- Hard-coded Lua pieces -------------------------------------------------------
1212

1313
prim Statement
14-
prim = local1 (Name.join2 [name|Prim|] [name|undefined|]) Nil
14+
prim = assignVar (primName [name|undefined|]) Nil
15+
16+
primName Name Name
17+
primName = psluaName . Name.join2 [name|Prim|]
18+
19+
uniqueName MonadState Natural m Text m Name
20+
uniqueName prefix = do
21+
index get
22+
modify' (+ 1)
23+
pure $ unsafeName (prefix <> show index)
24+
25+
psluaName Name Name
26+
psluaName = Name.join2 [name|PSLUA|]
1527

1628
runtimeLazyName Name
17-
runtimeLazyName = [name|_S___runtime_lazy|]
29+
runtimeLazyName = psluaName [name|runtime_lazy|]
1830

1931
runtimeLazy Statement
2032
runtimeLazy =
2133
ForeignSourceStat
22-
[__i| local function #{Name.toText runtimeLazyName}(name)
34+
[__i| function #{Name.toText runtimeLazyName}(name)
2335
return function(init)
2436
return function()
2537
local state = 0
@@ -42,13 +54,13 @@ runtimeLazy =
4254
|]
4355

4456
objectUpdateName Name
45-
objectUpdateName = [name|_S___object_update|]
57+
objectUpdateName = psluaName [name|object_update|]
4658

4759
objectUpdate Statement
4860
objectUpdate =
4961
ForeignSourceStat
5062
[__i|
51-
local function #{Name.toText objectUpdateName}(o, patches)
63+
function #{Name.toText objectUpdateName}(o, patches)
5264
local o_copy = {}
5365
for k, v in pairs(o) do
5466
local patch_v = patches

lib/Language/PureScript/Backend/Lua/Name.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -122,4 +122,4 @@ reserved =
122122
]
123123

124124
join2 Name Name Name
125-
join2 (Name a) (Name b) = Name (a <> "_I_" <> b)
125+
join2 (Name a) (Name b) = Name (a <> "_" <> b)

lib/Language/PureScript/Backend/Lua/Types.hs

+3
Original file line numberDiff line numberDiff line change
@@ -235,6 +235,9 @@ var = Var . ann
235235
assign Var Exp Statement
236236
assign v e = Assign (ann v) (ann e)
237237

238+
assignVar :: Name -> Exp -> Statement
239+
assignVar name = assign (VarName name)
240+
238241
local Name Maybe Exp Statement
239242
local name expr = Local name (ann <$> expr)
240243

lib/Language/PureScript/Names.hs

+5-2
Original file line numberDiff line numberDiff line change
@@ -81,8 +81,11 @@ runIdent = \case
8181
UnusedIdent unusedIdent
8282
InternalIdent internalIdentData
8383
case internalIdentData of
84-
RuntimeLazyFactory "$__runtime_lazy"
85-
Lazy t "$__lazy_" <> t
84+
RuntimeLazyFactory runtimeLazyName
85+
Lazy t "PSLUA_lazy_" <> t
86+
87+
runtimeLazyName :: Text
88+
runtimeLazyName = "PSLUA_runtime_lazy"
8689

8790
unusedIdent Text
8891
unusedIdent = "$__unused"

scripts/golden_reset

+1
Original file line numberDiff line numberDiff line change
@@ -3,3 +3,4 @@
33
echo "Removing all golden files..."
44
rm -rf
55
find ./test/ps/output -name 'golden.*' -delete
6+
cabal test

test/Language/PureScript/Backend/Lua/DCE/Spec.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -100,15 +100,15 @@ spec = describe "Lua Dead Code Elimination" do
100100
DCE.eliminateDeadCode PreserveReturned chunk === chunk
101101

102102
test "Doesn't eliminate anything from runtimeLazy" do
103-
let name = [Lua.name|_S___runtime_lazy|]
103+
let name = Fixture.runtimeLazyName
104104
let chunk =
105105
[ Fixture.runtimeLazy
106106
, Lua.return (Lua.functionCall (Lua.varName name) [])
107107
]
108108
DCE.eliminateDeadCode PreserveReturned chunk === chunk
109109

110110
test "scopes" do
111-
let name = [Lua.name|_S___runtime_lazy|]
111+
let name = Fixture.runtimeLazyName
112112
let chunk =
113113
[ Lua.local1 name $
114114
Lua.Function

test/Language/PureScript/Backend/Lua/Golden/Spec.hs

+1
Original file line numberDiff line numberDiff line change
@@ -134,6 +134,7 @@ spec = do
134134
, "--no-unused" -- TODO: harden eventually
135135
, "--no-max-line-length"
136136
, "--formatter plain"
137+
, "--allow-defined"
137138
, toFilePath lua
138139
]
139140
(exitCode, out) readProcessInterleaved process

test/ps/output/Golden.Annotations.M1/golden.lua

+3-3
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
local Golden_Annotations_M1_I_foreign = (function()
1+
PSLUA_Golden_Annotations_M1_foreign = (function()
22
local step = 2
33
return {
44
dontInlineClosure = function(i)
@@ -11,6 +11,6 @@ local Golden_Annotations_M1_I_foreign = (function()
1111
end)()
1212
return {
1313
inlineMe = function(v) if 1 == v then return 2 else return v end end,
14-
dontInlineClosure = Golden_Annotations_M1_I_foreign.dontInlineClosure,
15-
inlineMeLambda = Golden_Annotations_M1_I_foreign.inlineMeLambda
14+
dontInlineClosure = PSLUA_Golden_Annotations_M1_foreign.dontInlineClosure,
15+
inlineMeLambda = PSLUA_Golden_Annotations_M1_foreign.inlineMeLambda
1616
}

test/ps/output/Golden.Annotations.M2/golden.lua

+2-2
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
local Golden_Annotations_M1_I_foreign = (function()
1+
PSLUA_Golden_Annotations_M1_foreign = (function()
22
local step = 2
33
return {
44
dontInlineClosure = function(i)
@@ -27,5 +27,5 @@ return {
2727
end
2828
end
2929
end,
30-
inlineIntoMe2 = Golden_Annotations_M1_I_foreign.dontInlineClosure(Golden_Annotations_M1_I_foreign.inlineMeLambda(Golden_Annotations_M1_I_foreign.inlineMeLambda(17)))
30+
inlineIntoMe2 = PSLUA_Golden_Annotations_M1_foreign.dontInlineClosure(PSLUA_Golden_Annotations_M1_foreign.inlineMeLambda(PSLUA_Golden_Annotations_M1_foreign.inlineMeLambda(17)))
3131
}

test/ps/output/Golden.CaseStatements.Test/golden.lua

+3-3
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,11 @@
1-
local Golden_Values_Test_I_f = function(unused0) return true end
1+
PSLUA_Golden_Values_Test_f = function(unused0) return true end
22
return {
33
a = 1,
44
b = "b",
55
c = (function()
66
local v = function(unused1) return 0 end
7-
if Golden_Values_Test_I_f(2) then
8-
if Golden_Values_Test_I_f(1) then return 42 else return v(true) end
7+
if PSLUA_Golden_Values_Test_f(2) then
8+
if PSLUA_Golden_Values_Test_f(1) then return 42 else return v(true) end
99
else
1010
return v(true)
1111
end
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
1-
local Golden_Foreign_Lib_I_foreign = { dead = -100, alive = 100 }
1+
PSLUA_Golden_Foreign_Lib_foreign = { dead = -100, alive = 100 }
22
return {
3-
dead = Golden_Foreign_Lib_I_foreign.dead,
4-
alive = Golden_Foreign_Lib_I_foreign.alive
3+
dead = PSLUA_Golden_Foreign_Lib_foreign.dead,
4+
alive = PSLUA_Golden_Foreign_Lib_foreign.alive
55
}
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,8 @@
1-
local Golden_Foreign_Test_I_foreign = (function()
1+
PSLUA_Golden_Foreign_Test_foreign = (function()
22
local fooBar = 42
33
return { foo = fooBar + 1, boo = fooBar + 2 }
44
end)()
55
return {
6-
foo = Golden_Foreign_Test_I_foreign.foo,
7-
baz = { [1] = Golden_Foreign_Test_I_foreign.boo, [2] = 100 }
6+
foo = PSLUA_Golden_Foreign_Test_foreign.foo,
7+
baz = { [1] = PSLUA_Golden_Foreign_Test_foreign.boo, [2] = 100 }
88
}

test/ps/output/Golden.HelloPrelude.Test/golden.ir

+7-7
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,7 @@ UberModule
3838
( PropName "Apply0", Abs Nothing ( ParamUnused Nothing )
3939
( App Nothing
4040
( Ref Nothing
41-
( Imported ( ModuleName "Effect" ) ( Name "$__lazy_applyEffect" ) ) 0
41+
( Imported ( ModuleName "Effect" ) ( Name "PSLUA_lazy_applyEffect" ) ) 0
4242
)
4343
( LiteralInt Nothing 0 )
4444
)
@@ -56,18 +56,18 @@ UberModule
5656
( PropName "Apply0", Abs Nothing ( ParamUnused Nothing )
5757
( App Nothing
5858
( Ref Nothing
59-
( Imported ( ModuleName "Effect" ) ( Name "$__lazy_applyEffect" ) ) 0
59+
( Imported ( ModuleName "Effect" ) ( Name "PSLUA_lazy_applyEffect" ) ) 0
6060
)
6161
( LiteralInt Nothing 0 )
6262
)
6363
)
6464
]
6565
),
6666
( QName
67-
{ qnameModuleName = ModuleName "Effect", qnameName = Name "$__lazy_functorEffect"
67+
{ qnameModuleName = ModuleName "Effect", qnameName = Name "PSLUA_lazy_functorEffect"
6868
}, App Nothing
6969
( App Nothing
70-
( Ref Nothing ( Local ( Name "$__runtime_lazy" ) ) 0 )
70+
( Ref Nothing ( Local ( Name "PSLUA_runtime_lazy" ) ) 0 )
7171
( LiteralString Nothing "functorEffect" )
7272
)
7373
( Abs Nothing ( ParamUnused Nothing )
@@ -106,10 +106,10 @@ UberModule
106106
)
107107
),
108108
( QName
109-
{ qnameModuleName = ModuleName "Effect", qnameName = Name "$__lazy_applyEffect"
109+
{ qnameModuleName = ModuleName "Effect", qnameName = Name "PSLUA_lazy_applyEffect"
110110
}, App Nothing
111111
( App Nothing
112-
( Ref Nothing ( Local ( Name "$__runtime_lazy" ) ) 0 )
112+
( Ref Nothing ( Local ( Name "PSLUA_runtime_lazy" ) ) 0 )
113113
( LiteralString Nothing "applyEffect" )
114114
)
115115
( Abs Nothing ( ParamUnused Nothing )
@@ -186,7 +186,7 @@ UberModule
186186
( PropName "Functor0", Abs Nothing ( ParamUnused Nothing )
187187
( App Nothing
188188
( Ref Nothing
189-
( Imported ( ModuleName "Effect" ) ( Name "$__lazy_functorEffect" ) ) 0
189+
( Imported ( ModuleName "Effect" ) ( Name "PSLUA_lazy_functorEffect" ) ) 0
190190
)
191191
( LiteralInt Nothing 0 )
192192
)
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
1-
local Prim_I_undefined = nil
2-
local function _S___runtime_lazy(name)
1+
PSLUA_Prim_undefined = nil
2+
function PSLUA_runtime_lazy(name)
33
return function(init)
44
return function()
55
local state = 0
@@ -19,7 +19,7 @@ local function _S___runtime_lazy(name)
1919
end
2020
end
2121
end
22-
local Effect_I_foreign = {
22+
PSLUA_Effect_foreign = {
2323
pureE = function(a)
2424
return function()
2525
return a
@@ -33,46 +33,50 @@ local Effect_I_foreign = {
3333
end
3434
end
3535
}
36-
local Control_Applicative_I_pure = function(dict) return dict.pure end
37-
local Effect_I_monadEffect
38-
local Effect_I_bindEffect
39-
local Effect_I_applicativeEffect
40-
local Effect_I__S___lazy_functorEffect
41-
local Effect_I__S___lazy_applyEffect
42-
Effect_I_monadEffect = {
43-
Applicative0 = function(unused0) return Effect_I_applicativeEffect end,
44-
Bind1 = function(unused1) return Effect_I_bindEffect end
36+
PSLUA_Control_Applicative_pure = function(dict) return dict.pure end
37+
local PSLUA_Effect_monadEffect
38+
local PSLUA_Effect_bindEffect
39+
local PSLUA_Effect_applicativeEffect
40+
local PSLUA_Effect_PSLUA_lazy_functorEffect
41+
local PSLUA_Effect_PSLUA_lazy_applyEffect
42+
PSLUA_Effect_monadEffect = {
43+
Applicative0 = function(unused0) return PSLUA_Effect_applicativeEffect end,
44+
Bind1 = function(unused1) return PSLUA_Effect_bindEffect end
4545
}
46-
Effect_I_bindEffect = {
47-
bind = Effect_I_foreign.bindE,
48-
Apply0 = function(unused2) return Effect_I__S___lazy_applyEffect(0) end
46+
PSLUA_Effect_bindEffect = {
47+
bind = PSLUA_Effect_foreign.bindE,
48+
Apply0 = function(unused2) return PSLUA_Effect_PSLUA_lazy_applyEffect(0) end
4949
}
50-
Effect_I_applicativeEffect = {
51-
pure = Effect_I_foreign.pureE,
52-
Apply0 = function(unused3) return Effect_I__S___lazy_applyEffect(0) end
50+
PSLUA_Effect_applicativeEffect = {
51+
pure = PSLUA_Effect_foreign.pureE,
52+
Apply0 = function(unused3) return PSLUA_Effect_PSLUA_lazy_applyEffect(0) end
5353
}
54-
Effect_I__S___lazy_functorEffect = _S___runtime_lazy("functorEffect")(function( unused4 )
54+
PSLUA_Effect_PSLUA_lazy_functorEffect = PSLUA_runtime_lazy("functorEffect")(function( unused4 )
5555
return {
5656
map = function(f)
57-
return (Effect_I_applicativeEffect.Apply0(Prim_I_undefined)).apply(Control_Applicative_I_pure(Effect_I_applicativeEffect)(f))
57+
return (PSLUA_Effect_applicativeEffect.Apply0(PSLUA_Prim_undefined)).apply(PSLUA_Control_Applicative_pure(PSLUA_Effect_applicativeEffect)(f))
5858
end
5959
}
6060
end)
61-
Effect_I__S___lazy_applyEffect = _S___runtime_lazy("applyEffect")(function( unused6 )
61+
PSLUA_Effect_PSLUA_lazy_applyEffect = PSLUA_runtime_lazy("applyEffect")(function( unused6 )
6262
return {
6363
apply = (function()
6464
return function(f)
65-
local bind = (Effect_I_monadEffect.Bind1(Prim_I_undefined)).bind
65+
local bind = (PSLUA_Effect_monadEffect.Bind1(PSLUA_Prim_undefined)).bind
6666
return function(a)
6767
return bind(f)(function(fPrime)
6868
return bind(a)(function(aPrime)
69-
return Control_Applicative_I_pure(Effect_I_monadEffect.Applicative0(Prim_I_undefined))(fPrime(aPrime))
69+
return PSLUA_Control_Applicative_pure(PSLUA_Effect_monadEffect.Applicative0(PSLUA_Prim_undefined))(fPrime(aPrime))
7070
end)
7171
end)
7272
end
7373
end
7474
end)(),
75-
Functor0 = function(unused5) return Effect_I__S___lazy_functorEffect(0) end
75+
Functor0 = function(unused5)
76+
return PSLUA_Effect_PSLUA_lazy_functorEffect(0)
77+
end
7678
}
7779
end)
78-
return { main = Control_Applicative_I_pure(Effect_I_applicativeEffect)(nil) }
80+
return {
81+
main = PSLUA_Control_Applicative_pure(PSLUA_Effect_applicativeEffect)(nil)
82+
}
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,13 @@
1-
local Golden_NameShadowing_Test_I_f = function(v)
1+
PSLUA_Golden_NameShadowing_Test_f = function(v)
22
return function(v1)
33
if 1 == v then return 1 else if 1 == v1 then return 2 else return 3 end end
44
end
55
end
66
return {
77
b = function(x)
88
return function(x1)
9-
return Golden_NameShadowing_Test_I_f(Golden_NameShadowing_Test_I_f(x)(x1))(Golden_NameShadowing_Test_I_f(42)(1))
9+
return PSLUA_Golden_NameShadowing_Test_f(PSLUA_Golden_NameShadowing_Test_f(x)(x1))(PSLUA_Golden_NameShadowing_Test_f(42)(1))
1010
end
1111
end,
12-
c = Golden_NameShadowing_Test_I_f
12+
c = PSLUA_Golden_NameShadowing_Test_f
1313
}

0 commit comments

Comments
 (0)