Skip to content

Commit

Permalink
better have embedded Testcases....
Browse files Browse the repository at this point in the history
  • Loading branch information
thma committed Sep 14, 2023
1 parent c3dfa45 commit 21f2d45
Show file tree
Hide file tree
Showing 5 changed files with 56 additions and 31 deletions.
1 change: 1 addition & 0 deletions lambda-ski.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -78,6 +78,7 @@ test-suite lambda-ski-test
GraphReductionSpec
ReducerKiselyovSpec
ReducerSpec
TestSources
Paths_lambda_ski
hs-source-dirs:
test
Expand Down
20 changes: 10 additions & 10 deletions test/GraphReductionSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ import Test.QuickCheck
import Test.Hspec
import Control.Monad.ST (runST, ST)
import Data.STRef
import TestSources

main :: IO ()
main = hspec spec
Expand All @@ -18,26 +19,25 @@ spec :: Spec
spec =
describe "Classic GraphReduction with STRef" $ do
it "computes factorial" $
verify "factorial"
verify factorial
it "computes fibonacci" $
verify "fibonacci"
verify fibonacci
it "computes gaussian sum" $
verify "gaussian"
verify gaussian
it "computes ackermann function" $
verify "ackermann"
verify ackermann
it "computes tak " $
verify "tak"
verify tak

verify :: FilePath -> IO ()
verify tc = do
source <- loadTestCase tc
verify :: String -> IO ()
verify source = do
let (expected, actual) = runTest source
actual `shouldBe` expected

type SourceCode = String

loadTestCase :: String -> IO SourceCode
loadTestCase name = readFile $ "test/" ++ name ++ ".ths"
-- loadTestCase :: String -> IO SourceCode
-- loadTestCase name = readFile $ "test/" ++ name ++ ".ths"

getInt :: Expr -> Integer
getInt (Int i) = i
Expand Down
20 changes: 10 additions & 10 deletions test/ReducerKiselyovSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@ import Data.Maybe (fromJust)

import Test.QuickCheck
import Test.Hspec
import TestSources

main :: IO ()
main = hspec spec
Expand All @@ -16,27 +17,26 @@ spec :: Spec
spec =
describe "hhi inspired Reducer (Kiselyov compiler)" $ do
it "computes factorial" $
verify "factorial"
verify factorial
it "computes fibonacci" $
verify "fibonacci"
verify fibonacci
it "computes gaussian sum" $
verify "gaussian"
verify gaussian
it "computes ackermann function" $
verify "ackermann"
verify ackermann
it "computes tak " $
verify "tak"
verify tak


verify :: FilePath -> IO ()
verify tc = do
src <- loadTestCase tc
verify :: String -> IO ()
verify src = do
showCode src
src `shouldSatisfy` runTest

type SourceCode = String

loadTestCase :: String -> IO SourceCode
loadTestCase name = readFile $ "test/" ++ name ++ ".ths"
-- loadTestCase :: String -> IO SourceCode
-- loadTestCase name = readFile $ "test/" ++ name ++ ".ths"

showCode :: SourceCode -> IO ()
showCode src = do
Expand Down
20 changes: 9 additions & 11 deletions test/ReducerSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,7 @@ import Parser
import CLTerm
import LambdaToSKI
import Data.Maybe (fromJust)
--import TestSources
-- ( ackermann, factorial, fibonacci, gaussian, tak )
import TestSources

import Test.QuickCheck
import Test.Hspec
Expand All @@ -18,26 +17,25 @@ spec :: Spec
spec =
describe "hhi inspired Reducer " $ do
it "computes factorial" $
verify "factorial"
verify factorial
it "computes fibonacci" $
verify "fibonacci"
verify fibonacci
it "computes gaussian sum" $
verify "gaussian"
verify gaussian
it "computes ackermann function" $
verify "ackermann"
verify ackermann
it "computes tak " $
verify "tak"
verify tak


verify :: FilePath -> IO ()
verify tc = do
src <- loadTestCase tc
verify src = do
src `shouldSatisfy` runTest

type SourceCode = String

loadTestCase :: String -> IO SourceCode
loadTestCase name = readFile $ "test/" ++ name ++ ".ths"
-- loadTestCase :: String -> IO SourceCode
-- loadTestCase name = readFile $ "test/" ++ name ++ ".ths"

runTest :: SourceCode -> Bool
runTest src =
Expand Down
26 changes: 26 additions & 0 deletions test/TestSources.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,26 @@
module TestSources where

ackermann :: String
ackermann = "expected = 7 \n" ++
"ack = y(λf n m -> if (is0 n) (+ m 1) (if (is0 m) (f (sub1 n) 1) (f (sub1 n) (f n (sub1 m)))))\n" ++
"main = ack 2 2"

factorial :: String
factorial = "expected = 93326215443944152681699238856266700490715968264381621468592963895217599993229915608941463976156518286253697920827223758251185210916864000000000000000000000000\n" ++
"fact = y(λf n -> if (is0 n) 1 (* n (f (sub1 n))))\n" ++
"main = fact 100"

fibonacci :: String
fibonacci = "expected = 89\n" ++
"fib = y(λf n -> if (is0 n) 1 (if (eql n 1) 1 (+ (f (sub1 n)) (f (sub n 2)))))\n" ++
"main = fib 10"

gaussian :: String
gaussian = "expected = 5050\n" ++
"gaussianSum = y(λf n -> (if (is0 n) 0 (+ n (f (sub1 n)))))\n" ++
"main = gaussianSum 100"

tak :: String
tak = "expected = 4\n" ++
"tak = y(λf x y z -> (if (geq y x) z (f (f (sub1 x) y z) (f (sub1 y) z x) (f (sub1 z) x y ))))\n" ++
"main = tak 18 6 3"

0 comments on commit 21f2d45

Please sign in to comment.