Skip to content

Commit

Permalink
Fibonacci evaluation test
Browse files Browse the repository at this point in the history
  • Loading branch information
Unisay committed Apr 26, 2024
1 parent 7035386 commit bef2ba6
Show file tree
Hide file tree
Showing 6 changed files with 173 additions and 0 deletions.
13 changes: 13 additions & 0 deletions test/ps/golden/Golden/Fibonacci/Test.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
module Golden.Fibonacci.Test where

import Prelude
import Effect (Effect)
import Effect.Console (logShow)

fib :: Int -> Int
fib 0 = 0
fib 1 = 1
fib n = fib (n - 1) + fib (n - 2)

main :: Effect Unit
main = logShow $ fib 32 -- 2178309
1 change: 1 addition & 0 deletions test/ps/output/Golden.Fibonacci.Test/corefn.json
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
{"builtWith":"0.15.15","comments":[],"decls":[{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":{"metaType":"IsForeign"},"sourceSpan":{"end":[10,22],"start":[10,21]}},"type":"Var","value":{"identifier":"add","moduleName":["Data","Semiring"]}},"annotation":{"meta":{"metaType":"IsSyntheticApp"},"sourceSpan":{"end":[10,34],"start":[10,9]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"type":"Var","value":{"identifier":"semiringInt","moduleName":["Data","Semiring"]}},"type":"App"},"identifier":"add"},{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":{"metaType":"IsForeign"},"sourceSpan":{"end":[10,17],"start":[10,16]}},"type":"Var","value":{"identifier":"sub","moduleName":["Data","Ring"]}},"annotation":{"meta":{"metaType":"IsSyntheticApp"},"sourceSpan":{"end":[10,19],"start":[10,14]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"type":"Var","value":{"identifier":"ringInt","moduleName":["Data","Ring"]}},"type":"App"},"identifier":"sub"},{"bindType":"Rec","binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[7,18],"start":[7,1]}},"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[7,18],"start":[7,1]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[7,18],"start":[7,1]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[8,6],"start":[8,5]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":0}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[8,10],"start":[8,9]}},"type":"Literal","value":{"literalType":"IntLiteral","value":0}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[9,6],"start":[9,5]}},"binderType":"LiteralBinder","literal":{"literalType":"IntLiteral","value":1}}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[9,10],"start":[9,9]}},"type":"Literal","value":{"literalType":"IntLiteral","value":1}},"isGuarded":false},{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[10,6],"start":[10,5]}},"binderType":"VarBinder","identifier":"n"}],"expression":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"type":"Var","value":{"identifier":"add","moduleName":["Golden","Fibonacci","Test"]}},"annotation":{"meta":null,"sourceSpan":{"end":[10,34],"start":[10,9]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[10,12],"start":[10,9]}},"type":"Var","value":{"identifier":"fib","moduleName":["Golden","Fibonacci","Test"]}},"annotation":{"meta":null,"sourceSpan":{"end":[10,20],"start":[10,9]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"type":"Var","value":{"identifier":"sub","moduleName":["Golden","Fibonacci","Test"]}},"annotation":{"meta":null,"sourceSpan":{"end":[10,19],"start":[10,14]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[10,15],"start":[10,14]}},"type":"Var","value":{"identifier":"n","sourcePos":[10,5]}},"type":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[10,19],"start":[10,14]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[10,19],"start":[10,18]}},"type":"Literal","value":{"literalType":"IntLiteral","value":1}},"type":"App"},"type":"App"},"type":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[10,34],"start":[10,9]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[10,26],"start":[10,23]}},"type":"Var","value":{"identifier":"fib","moduleName":["Golden","Fibonacci","Test"]}},"annotation":{"meta":null,"sourceSpan":{"end":[10,34],"start":[10,23]}},"argument":{"abstraction":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"type":"Var","value":{"identifier":"sub","moduleName":["Golden","Fibonacci","Test"]}},"annotation":{"meta":null,"sourceSpan":{"end":[10,33],"start":[10,28]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[10,29],"start":[10,28]}},"type":"Var","value":{"identifier":"n","sourcePos":[10,5]}},"type":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[10,33],"start":[10,28]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[10,33],"start":[10,32]}},"type":"Literal","value":{"literalType":"IntLiteral","value":2}},"type":"App"},"type":"App"},"type":"App"},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[8,10],"start":[8,1]}},"type":"Var","value":{"identifier":"v","sourcePos":[0,0]}}],"type":"Case"},"type":"Abs"},"identifier":"fib"}]},{"annotation":{"meta":null,"sourceSpan":{"end":[12,20],"start":[12,1]}},"bindType":"NonRec","expression":{"abstraction":{"abstraction":{"annotation":{"meta":{"metaType":"IsForeign"},"sourceSpan":{"end":[13,15],"start":[13,8]}},"type":"Var","value":{"identifier":"logShow","moduleName":["Effect","Console"]}},"annotation":{"meta":{"metaType":"IsSyntheticApp"},"sourceSpan":{"end":[13,15],"start":[13,8]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[0,0],"start":[0,0]}},"type":"Var","value":{"identifier":"showInt","moduleName":["Data","Show"]}},"type":"App"},"annotation":{"meta":null,"sourceSpan":{"end":[13,24],"start":[13,8]}},"argument":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[13,21],"start":[13,18]}},"type":"Var","value":{"identifier":"fib","moduleName":["Golden","Fibonacci","Test"]}},"annotation":{"meta":null,"sourceSpan":{"end":[13,24],"start":[13,18]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[13,24],"start":[13,22]}},"type":"Literal","value":{"literalType":"IntLiteral","value":32}},"type":"App"},"type":"App"},"identifier":"main"}],"exports":["fib","main"],"foreign":[],"imports":[{"annotation":{"meta":null,"sourceSpan":{"end":[13,24],"start":[1,1]}},"moduleName":["Data","Function"]},{"annotation":{"meta":null,"sourceSpan":{"end":[13,24],"start":[1,1]}},"moduleName":["Data","Ring"]},{"annotation":{"meta":null,"sourceSpan":{"end":[13,24],"start":[1,1]}},"moduleName":["Data","Semiring"]},{"annotation":{"meta":null,"sourceSpan":{"end":[13,24],"start":[1,1]}},"moduleName":["Data","Show"]},{"annotation":{"meta":null,"sourceSpan":{"end":[4,23],"start":[4,1]}},"moduleName":["Effect"]},{"annotation":{"meta":null,"sourceSpan":{"end":[13,24],"start":[1,1]}},"moduleName":["Effect","Console"]},{"annotation":{"meta":null,"sourceSpan":{"end":[13,24],"start":[1,1]}},"moduleName":["Golden","Fibonacci","Test"]},{"annotation":{"meta":null,"sourceSpan":{"end":[3,15],"start":[3,1]}},"moduleName":["Prelude"]},{"annotation":{"meta":null,"sourceSpan":{"end":[13,24],"start":[1,1]}},"moduleName":["Prim"]}],"moduleName":["Golden","Fibonacci","Test"],"modulePath":"golden/Golden/Fibonacci/Test.purs","reExports":{},"sourceSpan":{"end":[13,24],"start":[1,1]}}
1 change: 1 addition & 0 deletions test/ps/output/Golden.Fibonacci.Test/eval/.gitignore
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
actual.txt
1 change: 1 addition & 0 deletions test/ps/output/Golden.Fibonacci.Test/eval/golden.txt
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
2178309
133 changes: 133 additions & 0 deletions test/ps/output/Golden.Fibonacci.Test/golden.ir
Original file line number Diff line number Diff line change
@@ -0,0 +1,133 @@
UberModule
{ uberModuleBindings =
[ Standalone
( QName
{ qnameModuleName = ModuleName "Data.Semiring", qnameName = Name "foreign"
}, ForeignImport Nothing
( ModuleName "Data.Semiring" ) ".spago/prelude/v7.2.0/src/Data/Semiring.purs"
[ ( Nothing, Name "intAdd" ), ( Nothing, Name "intMul" ) ]
), Standalone
( QName
{ qnameModuleName = ModuleName "Data.Semiring", qnameName = Name "semiringInt"
}, LiteralObject Nothing
[
( PropName "add", ObjectProp ( Just Always )
( Ref Nothing ( Imported ( ModuleName "Data.Semiring" ) ( Name "foreign" ) ) 0 )
( PropName "intAdd" )
),
( PropName "zero", LiteralInt Nothing 0 ),
( PropName "mul", ObjectProp ( Just Always )
( Ref Nothing ( Imported ( ModuleName "Data.Semiring" ) ( Name "foreign" ) ) 0 )
( PropName "intMul" )
),
( PropName "one", LiteralInt Nothing 1 )
]
), Standalone
( QName
{ qnameModuleName = ModuleName "Golden.Fibonacci.Test", qnameName = Name "sub"
}, ObjectProp Nothing
( LiteralObject Nothing
[
( PropName "sub", ObjectProp ( Just Always )
( ForeignImport Nothing
( ModuleName "Data.Ring" ) ".spago/prelude/v7.2.0/src/Data/Ring.purs"
[ ( Nothing, Name "intSub" ) ]
)
( PropName "intSub" )
),
( PropName "Semiring0", Abs Nothing ( ParamUnused Nothing )
( Ref Nothing ( Imported ( ModuleName "Data.Semiring" ) ( Name "semiringInt" ) ) 0 )
)
]
)
( PropName "sub" )
), RecursiveGroup
(
( QName
{ qnameModuleName = ModuleName "Golden.Fibonacci.Test", qnameName = Name "fib"
}, Abs Nothing
( ParamNamed Nothing ( Name "v" ) )
( IfThenElse Nothing
( Eq Nothing ( LiteralInt Nothing 0 ) ( Ref Nothing ( Local ( Name "v" ) ) 0 ) )
( LiteralInt Nothing 0 )
( IfThenElse Nothing
( Eq Nothing ( LiteralInt Nothing 1 ) ( Ref Nothing ( Local ( Name "v" ) ) 0 ) )
( LiteralInt Nothing 1 )
( App Nothing
( App Nothing
( ObjectProp Nothing
( Ref Nothing
( Imported ( ModuleName "Data.Semiring" ) ( Name "semiringInt" ) ) 0
)
( PropName "add" )
)
( App Nothing
( Ref Nothing
( Imported ( ModuleName "Golden.Fibonacci.Test" ) ( Name "fib" ) ) 0
)
( App Nothing
( App Nothing
( Ref Nothing
( Imported ( ModuleName "Golden.Fibonacci.Test" ) ( Name "sub" ) ) 0
)
( Ref Nothing ( Local ( Name "v" ) ) 0 )
)
( LiteralInt Nothing 1 )
)
)
)
( App Nothing
( Ref Nothing
( Imported ( ModuleName "Golden.Fibonacci.Test" ) ( Name "fib" ) ) 0
)
( App Nothing
( App Nothing
( Ref Nothing
( Imported ( ModuleName "Golden.Fibonacci.Test" ) ( Name "sub" ) ) 0
)
( Ref Nothing ( Local ( Name "v" ) ) 0 )
)
( LiteralInt Nothing 2 )
)
)
)
)
)
) :| []
)
], uberModuleForeigns = [], uberModuleExports =
[
( Name "fib", Ref Nothing
( Imported ( ModuleName "Golden.Fibonacci.Test" ) ( Name "fib" ) ) 0
),
( Name "main", App Nothing
( ObjectProp ( Just Always )
( ForeignImport Nothing
( ModuleName "Effect.Console" ) ".spago/console/v6.1.0/src/Effect/Console.purs"
[ ( Nothing, Name "log" ) ]
)
( PropName "log" )
)
( App Nothing
( ObjectProp Nothing
( LiteralObject Nothing
[
( PropName "show", ObjectProp ( Just Always )
( ForeignImport Nothing
( ModuleName "Data.Show" ) ".spago/prelude/v7.2.0/src/Data/Show.purs"
[ ( Nothing, Name "showIntImpl" ) ]
)
( PropName "showIntImpl" )
)
]
)
( PropName "show" )
)
( App Nothing
( Ref Nothing ( Imported ( ModuleName "Golden.Fibonacci.Test" ) ( Name "fib" ) ) 0 )
( LiteralInt Nothing 32 )
)
)
)
]
}
24 changes: 24 additions & 0 deletions test/ps/output/Golden.Fibonacci.Test/golden.lua
Original file line number Diff line number Diff line change
@@ -0,0 +1,24 @@
local M = {}
M.Data_Semiring_foreign = {
intAdd = function(x) return function(y) return x + y end end,
intMul = function(x) return function(y) return x * y end end
}
M.Data_Semiring_semiringInt = {
add = M.Data_Semiring_foreign.intAdd,
zero = 0,
mul = M.Data_Semiring_foreign.intMul,
one = 1
}
M.Golden_Fibonacci_Test_sub = function(x) return function(y) return x - y end end
M.Golden_Fibonacci_Test_fib = function(v)
if 0 == v then
return 0
else
if 1 == v then
return 1
else
return M.Data_Semiring_semiringInt.add(M.Golden_Fibonacci_Test_fib(M.Golden_Fibonacci_Test_sub(v)(1)))(M.Golden_Fibonacci_Test_fib(M.Golden_Fibonacci_Test_sub(v)(2)))
end
end
end
return (function(s) return function() print(s) end end)((function(n) return tostring(n) end)(M.Golden_Fibonacci_Test_fib(32)))()

0 comments on commit bef2ba6

Please sign in to comment.