Skip to content

Commit

Permalink
Make all bindings global
Browse files Browse the repository at this point in the history
  • Loading branch information
Unisay committed Apr 20, 2024
1 parent 7c7b7b7 commit c0dfe8a
Show file tree
Hide file tree
Showing 24 changed files with 139 additions and 111 deletions.
3 changes: 2 additions & 1 deletion lib/Language/PureScript/Backend/IR/Query.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ import Language.PureScript.Backend.IR.Types
, traverseExpBottomUp
)
import Language.PureScript.Backend.IR.Types qualified as IR
import Language.PureScript.Names (runtimeLazyName)

usesRuntimeLazy UberModule Bool
usesRuntimeLazy UberModule {uberModuleBindings, uberModuleExports} =
Expand All @@ -29,7 +30,7 @@ usesRuntimeLazy UberModule {uberModuleBindings, uberModuleExports} =

findRuntimeLazyInExpr Exp Bool
findRuntimeLazyInExpr expr =
countFreeRef (Local (Name "$__runtime_lazy")) expr > 0
countFreeRef (Local (Name runtimeLazyName)) expr > 0

usesPrimModule UberModule Bool
usesPrimModule UberModule {uberModuleBindings, uberModuleExports} =
Expand Down
15 changes: 7 additions & 8 deletions lib/Language/PureScript/Backend/Lua.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE QuasiQuotes #-}

module Language.PureScript.Backend.Lua
( fromUberModule
, fromIR
Expand Down Expand Up @@ -68,22 +70,19 @@ fromUberModule foreigns needsRuntimeLazy appOrModule uber = (`evalStateT` 0) do
foreignBindings
forM (Linker.uberModuleForeigns uber) \(IR.QName modname name, irExp) do
exp asExpression <$> fromIR foreigns Set.empty modname irExp
pure (Lua.local1 (fromQName modname name) exp)
pure $ Lua.assign (Lua.VarName (fromQName modname name)) exp
bindings
Linker.uberModuleBindings uber & foldMapM \case
IR.Standalone (IR.QName modname name, irExp) do
exp fromIR foreigns Set.empty modname irExp
pure $
DList.singleton
(Lua.local1 (fromQName modname name) (asExpression exp))
pure . DList.singleton $
Lua.assignVar (fromQName modname name) (asExpression exp)
IR.RecursiveGroup recGroup do
recBinds forM (toList recGroup) \(IR.QName modname name, irExp)
(fromQName modname name,) . asExpression
<$> fromIR foreigns Set.empty modname irExp
let declarations = Lua.local0 . fst <$> DList.fromList recBinds
assignments = DList.fromList do
recBinds <&> \(name, exp)
Lua.assign (Lua.VarName name) exp
assignments = DList.fromList (uncurry Lua.assignVar <$> recBinds)
pure $ declarations <> assignments

returnExp
Expand Down Expand Up @@ -282,4 +281,4 @@ uniqueName prefix = do
pure $ Lua.unsafeName (prefix <> show index)

qualifyName ModuleName Lua.Name Lua.Name
qualifyName modname = Name.join2 (fromModuleName modname)
qualifyName modname = Fixture.psluaName . Name.join2 (fromModuleName modname)
24 changes: 18 additions & 6 deletions lib/Language/PureScript/Backend/Lua/Fixture.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,23 +3,35 @@
module Language.PureScript.Backend.Lua.Fixture where

import Data.String.Interpolate (__i)
import Language.PureScript.Backend.Lua.Name (Name, name)
import Language.PureScript.Backend.Lua.Name (Name, name, unsafeName)
import Language.PureScript.Backend.Lua.Name qualified as Name
import Language.PureScript.Backend.Lua.Types hiding (var)

--------------------------------------------------------------------------------
-- Hard-coded Lua pieces -------------------------------------------------------

prim Statement
prim = local1 (Name.join2 [name|Prim|] [name|undefined|]) Nil
prim = assignVar (primName [name|undefined|]) Nil

primName Name Name
primName = psluaName . Name.join2 [name|Prim|]

uniqueName MonadState Natural m Text m Name
uniqueName prefix = do
index get
modify' (+ 1)
pure $ unsafeName (prefix <> show index)

psluaName Name Name
psluaName = Name.join2 [name|PSLUA|]

runtimeLazyName Name
runtimeLazyName = [name|_S___runtime_lazy|]
runtimeLazyName = psluaName [name|runtime_lazy|]

runtimeLazy Statement
runtimeLazy =
ForeignSourceStat
[__i| local function #{Name.toText runtimeLazyName}(name)
[__i| function #{Name.toText runtimeLazyName}(name)
return function(init)
return function()
local state = 0
Expand All @@ -42,13 +54,13 @@ runtimeLazy =
|]

objectUpdateName Name
objectUpdateName = [name|_S___object_update|]
objectUpdateName = psluaName [name|object_update|]

objectUpdate Statement
objectUpdate =
ForeignSourceStat
[__i|
local function #{Name.toText objectUpdateName}(o, patches)
function #{Name.toText objectUpdateName}(o, patches)
local o_copy = {}
for k, v in pairs(o) do
local patch_v = patches
Expand Down
2 changes: 1 addition & 1 deletion lib/Language/PureScript/Backend/Lua/Name.hs
Original file line number Diff line number Diff line change
Expand Up @@ -122,4 +122,4 @@ reserved =
]

join2 Name Name Name
join2 (Name a) (Name b) = Name (a <> "_I_" <> b)
join2 (Name a) (Name b) = Name (a <> "_" <> b)
3 changes: 3 additions & 0 deletions lib/Language/PureScript/Backend/Lua/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -235,6 +235,9 @@ var = Var . ann
assign Var Exp Statement
assign v e = Assign (ann v) (ann e)

assignVar :: Name -> Exp -> Statement
assignVar name = assign (VarName name)

local Name Maybe Exp Statement
local name expr = Local name (ann <$> expr)

Expand Down
7 changes: 5 additions & 2 deletions lib/Language/PureScript/Names.hs
Original file line number Diff line number Diff line change
Expand Up @@ -81,8 +81,11 @@ runIdent = \case
UnusedIdent unusedIdent
InternalIdent internalIdentData
case internalIdentData of
RuntimeLazyFactory "$__runtime_lazy"
Lazy t "$__lazy_" <> t
RuntimeLazyFactory runtimeLazyName
Lazy t "PSLUA_lazy_" <> t

runtimeLazyName :: Text
runtimeLazyName = "PSLUA_runtime_lazy"

unusedIdent Text
unusedIdent = "$__unused"
Expand Down
1 change: 1 addition & 0 deletions scripts/golden_reset
Original file line number Diff line number Diff line change
Expand Up @@ -3,3 +3,4 @@
echo "Removing all golden files..."
rm -rf
find ./test/ps/output -name 'golden.*' -delete
cabal test
4 changes: 2 additions & 2 deletions test/Language/PureScript/Backend/Lua/DCE/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -100,15 +100,15 @@ spec = describe "Lua Dead Code Elimination" do
DCE.eliminateDeadCode PreserveReturned chunk === chunk

test "Doesn't eliminate anything from runtimeLazy" do
let name = [Lua.name|_S___runtime_lazy|]
let name = Fixture.runtimeLazyName
let chunk =
[ Fixture.runtimeLazy
, Lua.return (Lua.functionCall (Lua.varName name) [])
]
DCE.eliminateDeadCode PreserveReturned chunk === chunk

test "scopes" do
let name = [Lua.name|_S___runtime_lazy|]
let name = Fixture.runtimeLazyName
let chunk =
[ Lua.local1 name $
Lua.Function
Expand Down
1 change: 1 addition & 0 deletions test/Language/PureScript/Backend/Lua/Golden/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -134,6 +134,7 @@ spec = do
, "--no-unused" -- TODO: harden eventually
, "--no-max-line-length"
, "--formatter plain"
, "--allow-defined"
, toFilePath lua
]
(exitCode, out) readProcessInterleaved process
Expand Down
6 changes: 3 additions & 3 deletions test/ps/output/Golden.Annotations.M1/golden.lua
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
local Golden_Annotations_M1_I_foreign = (function()
PSLUA_Golden_Annotations_M1_foreign = (function()
local step = 2
return {
dontInlineClosure = function(i)
Expand All @@ -11,6 +11,6 @@ local Golden_Annotations_M1_I_foreign = (function()
end)()
return {
inlineMe = function(v) if 1 == v then return 2 else return v end end,
dontInlineClosure = Golden_Annotations_M1_I_foreign.dontInlineClosure,
inlineMeLambda = Golden_Annotations_M1_I_foreign.inlineMeLambda
dontInlineClosure = PSLUA_Golden_Annotations_M1_foreign.dontInlineClosure,
inlineMeLambda = PSLUA_Golden_Annotations_M1_foreign.inlineMeLambda
}
4 changes: 2 additions & 2 deletions test/ps/output/Golden.Annotations.M2/golden.lua
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
local Golden_Annotations_M1_I_foreign = (function()
PSLUA_Golden_Annotations_M1_foreign = (function()
local step = 2
return {
dontInlineClosure = function(i)
Expand Down Expand Up @@ -27,5 +27,5 @@ return {
end
end
end,
inlineIntoMe2 = Golden_Annotations_M1_I_foreign.dontInlineClosure(Golden_Annotations_M1_I_foreign.inlineMeLambda(Golden_Annotations_M1_I_foreign.inlineMeLambda(17)))
inlineIntoMe2 = PSLUA_Golden_Annotations_M1_foreign.dontInlineClosure(PSLUA_Golden_Annotations_M1_foreign.inlineMeLambda(PSLUA_Golden_Annotations_M1_foreign.inlineMeLambda(17)))
}
6 changes: 3 additions & 3 deletions test/ps/output/Golden.CaseStatements.Test/golden.lua
Original file line number Diff line number Diff line change
@@ -1,11 +1,11 @@
local Golden_Values_Test_I_f = function(unused0) return true end
PSLUA_Golden_Values_Test_f = function(unused0) return true end
return {
a = 1,
b = "b",
c = (function()
local v = function(unused1) return 0 end
if Golden_Values_Test_I_f(2) then
if Golden_Values_Test_I_f(1) then return 42 else return v(true) end
if PSLUA_Golden_Values_Test_f(2) then
if PSLUA_Golden_Values_Test_f(1) then return 42 else return v(true) end
else
return v(true)
end
Expand Down
6 changes: 3 additions & 3 deletions test/ps/output/Golden.Foreign.Lib/golden.lua
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
local Golden_Foreign_Lib_I_foreign = { dead = -100, alive = 100 }
PSLUA_Golden_Foreign_Lib_foreign = { dead = -100, alive = 100 }
return {
dead = Golden_Foreign_Lib_I_foreign.dead,
alive = Golden_Foreign_Lib_I_foreign.alive
dead = PSLUA_Golden_Foreign_Lib_foreign.dead,
alive = PSLUA_Golden_Foreign_Lib_foreign.alive
}
6 changes: 3 additions & 3 deletions test/ps/output/Golden.Foreign.Test/golden.lua
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
local Golden_Foreign_Test_I_foreign = (function()
PSLUA_Golden_Foreign_Test_foreign = (function()
local fooBar = 42
return { foo = fooBar + 1, boo = fooBar + 2 }
end)()
return {
foo = Golden_Foreign_Test_I_foreign.foo,
baz = { [1] = Golden_Foreign_Test_I_foreign.boo, [2] = 100 }
foo = PSLUA_Golden_Foreign_Test_foreign.foo,
baz = { [1] = PSLUA_Golden_Foreign_Test_foreign.boo, [2] = 100 }
}
14 changes: 7 additions & 7 deletions test/ps/output/Golden.HelloPrelude.Test/golden.ir
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ UberModule
( PropName "Apply0", Abs Nothing ( ParamUnused Nothing )
( App Nothing
( Ref Nothing
( Imported ( ModuleName "Effect" ) ( Name "$__lazy_applyEffect" ) ) 0
( Imported ( ModuleName "Effect" ) ( Name "PSLUA_lazy_applyEffect" ) ) 0
)
( LiteralInt Nothing 0 )
)
Expand All @@ -56,18 +56,18 @@ UberModule
( PropName "Apply0", Abs Nothing ( ParamUnused Nothing )
( App Nothing
( Ref Nothing
( Imported ( ModuleName "Effect" ) ( Name "$__lazy_applyEffect" ) ) 0
( Imported ( ModuleName "Effect" ) ( Name "PSLUA_lazy_applyEffect" ) ) 0
)
( LiteralInt Nothing 0 )
)
)
]
),
( QName
{ qnameModuleName = ModuleName "Effect", qnameName = Name "$__lazy_functorEffect"
{ qnameModuleName = ModuleName "Effect", qnameName = Name "PSLUA_lazy_functorEffect"
}, App Nothing
( App Nothing
( Ref Nothing ( Local ( Name "$__runtime_lazy" ) ) 0 )
( Ref Nothing ( Local ( Name "PSLUA_runtime_lazy" ) ) 0 )
( LiteralString Nothing "functorEffect" )
)
( Abs Nothing ( ParamUnused Nothing )
Expand Down Expand Up @@ -106,10 +106,10 @@ UberModule
)
),
( QName
{ qnameModuleName = ModuleName "Effect", qnameName = Name "$__lazy_applyEffect"
{ qnameModuleName = ModuleName "Effect", qnameName = Name "PSLUA_lazy_applyEffect"
}, App Nothing
( App Nothing
( Ref Nothing ( Local ( Name "$__runtime_lazy" ) ) 0 )
( Ref Nothing ( Local ( Name "PSLUA_runtime_lazy" ) ) 0 )
( LiteralString Nothing "applyEffect" )
)
( Abs Nothing ( ParamUnused Nothing )
Expand Down Expand Up @@ -186,7 +186,7 @@ UberModule
( PropName "Functor0", Abs Nothing ( ParamUnused Nothing )
( App Nothing
( Ref Nothing
( Imported ( ModuleName "Effect" ) ( Name "$__lazy_functorEffect" ) ) 0
( Imported ( ModuleName "Effect" ) ( Name "PSLUA_lazy_functorEffect" ) ) 0
)
( LiteralInt Nothing 0 )
)
Expand Down
54 changes: 29 additions & 25 deletions test/ps/output/Golden.HelloPrelude.Test/golden.lua
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
local Prim_I_undefined = nil
local function _S___runtime_lazy(name)
PSLUA_Prim_undefined = nil
function PSLUA_runtime_lazy(name)
return function(init)
return function()
local state = 0
Expand All @@ -19,7 +19,7 @@ local function _S___runtime_lazy(name)
end
end
end
local Effect_I_foreign = {
PSLUA_Effect_foreign = {
pureE = function(a)
return function()
return a
Expand All @@ -33,46 +33,50 @@ local Effect_I_foreign = {
end
end
}
local Control_Applicative_I_pure = function(dict) return dict.pure end
local Effect_I_monadEffect
local Effect_I_bindEffect
local Effect_I_applicativeEffect
local Effect_I__S___lazy_functorEffect
local Effect_I__S___lazy_applyEffect
Effect_I_monadEffect = {
Applicative0 = function(unused0) return Effect_I_applicativeEffect end,
Bind1 = function(unused1) return Effect_I_bindEffect end
PSLUA_Control_Applicative_pure = function(dict) return dict.pure end
local PSLUA_Effect_monadEffect
local PSLUA_Effect_bindEffect
local PSLUA_Effect_applicativeEffect
local PSLUA_Effect_PSLUA_lazy_functorEffect
local PSLUA_Effect_PSLUA_lazy_applyEffect
PSLUA_Effect_monadEffect = {
Applicative0 = function(unused0) return PSLUA_Effect_applicativeEffect end,
Bind1 = function(unused1) return PSLUA_Effect_bindEffect end
}
Effect_I_bindEffect = {
bind = Effect_I_foreign.bindE,
Apply0 = function(unused2) return Effect_I__S___lazy_applyEffect(0) end
PSLUA_Effect_bindEffect = {
bind = PSLUA_Effect_foreign.bindE,
Apply0 = function(unused2) return PSLUA_Effect_PSLUA_lazy_applyEffect(0) end
}
Effect_I_applicativeEffect = {
pure = Effect_I_foreign.pureE,
Apply0 = function(unused3) return Effect_I__S___lazy_applyEffect(0) end
PSLUA_Effect_applicativeEffect = {
pure = PSLUA_Effect_foreign.pureE,
Apply0 = function(unused3) return PSLUA_Effect_PSLUA_lazy_applyEffect(0) end
}
Effect_I__S___lazy_functorEffect = _S___runtime_lazy("functorEffect")(function( unused4 )
PSLUA_Effect_PSLUA_lazy_functorEffect = PSLUA_runtime_lazy("functorEffect")(function( unused4 )
return {
map = function(f)
return (Effect_I_applicativeEffect.Apply0(Prim_I_undefined)).apply(Control_Applicative_I_pure(Effect_I_applicativeEffect)(f))
return (PSLUA_Effect_applicativeEffect.Apply0(PSLUA_Prim_undefined)).apply(PSLUA_Control_Applicative_pure(PSLUA_Effect_applicativeEffect)(f))
end
}
end)
Effect_I__S___lazy_applyEffect = _S___runtime_lazy("applyEffect")(function( unused6 )
PSLUA_Effect_PSLUA_lazy_applyEffect = PSLUA_runtime_lazy("applyEffect")(function( unused6 )
return {
apply = (function()
return function(f)
local bind = (Effect_I_monadEffect.Bind1(Prim_I_undefined)).bind
local bind = (PSLUA_Effect_monadEffect.Bind1(PSLUA_Prim_undefined)).bind
return function(a)
return bind(f)(function(fPrime)
return bind(a)(function(aPrime)
return Control_Applicative_I_pure(Effect_I_monadEffect.Applicative0(Prim_I_undefined))(fPrime(aPrime))
return PSLUA_Control_Applicative_pure(PSLUA_Effect_monadEffect.Applicative0(PSLUA_Prim_undefined))(fPrime(aPrime))
end)
end)
end
end
end)(),
Functor0 = function(unused5) return Effect_I__S___lazy_functorEffect(0) end
Functor0 = function(unused5)
return PSLUA_Effect_PSLUA_lazy_functorEffect(0)
end
}
end)
return { main = Control_Applicative_I_pure(Effect_I_applicativeEffect)(nil) }
return {
main = PSLUA_Control_Applicative_pure(PSLUA_Effect_applicativeEffect)(nil)
}
6 changes: 3 additions & 3 deletions test/ps/output/Golden.NameShadowing.Test/golden.lua
Original file line number Diff line number Diff line change
@@ -1,13 +1,13 @@
local Golden_NameShadowing_Test_I_f = function(v)
PSLUA_Golden_NameShadowing_Test_f = function(v)
return function(v1)
if 1 == v then return 1 else if 1 == v1 then return 2 else return 3 end end
end
end
return {
b = function(x)
return function(x1)
return Golden_NameShadowing_Test_I_f(Golden_NameShadowing_Test_I_f(x)(x1))(Golden_NameShadowing_Test_I_f(42)(1))
return PSLUA_Golden_NameShadowing_Test_f(PSLUA_Golden_NameShadowing_Test_f(x)(x1))(PSLUA_Golden_NameShadowing_Test_f(42)(1))
end
end,
c = Golden_NameShadowing_Test_I_f
c = PSLUA_Golden_NameShadowing_Test_f
}
Loading

0 comments on commit c0dfe8a

Please sign in to comment.