module Testing.Unit.ToPythonTests
    (tests, runU)
where

import Test.HUnit

import Data.Number.Sifflet
import Language.Sifflet.Expr (Expr(..), Function)
import Language.Sifflet.Export.Python
import Language.Sifflet.Export.ToPython

import Testing.Unit.FunctionExamples
import Testing.TestUtil (assertAll, utestloop)

-- These tests functions should be replaced by those in Test.hs
-- converted to Python

pydef :: Function -> PStatement
pydef = functionToPyDef


pf1, pf2, pf3, pf4, pf5, pf6, pf7, pf8, pf9 :: PStatement

pf1 = pydef f1
pf2 = pydef f2
pf3 = pydef f3
pf4 = pydef f4
pf5 = pydef f5
pf6 = pydef f6
pf7 = pydef f7
pf8 = pydef f8
pf9 = pydef f9

pf10, pf11, pf12, pf13, pf14 :: PStatement

pf10 = pydef f10
pf11 = pydef f11
pf12 = pydef f12
pf13 = pydef f13
pf14 = pydef f14

tests :: Test
tests = 
    let toPy = pyPretty -- was: pretty . alterParens bestParens
        tfunc label func result =
            assertEqual label result (toPy func)
        texpr label expr result =
            assertEqual label result (pyPretty (exprToPExpr expr))
        sixSeven = map (ENumber . Exact) [6, 7]
    in assertAll
           [
            tfunc "pf1" pf1 ("def foo():\n" ++
                           "    return 1")
           , tfunc "pf2" pf2 ("def bar(a, b, c):\n" ++
                            "    return a * b + c * 2")
           , tfunc "pf3" pf3 ("def cup(a, b, c):\n" ++
                            "    return (a + b) * (c + 2)")
           , tfunc "pf4" pf4 ("def dook(a, b, c):\n" ++
                            "    return a + b * c")
           , tfunc "pf5" pf5 
             ("def egg(x, y, z):\n" ++
              "    return x + y + (z + 7 if x < y else 1 + z * z)")
           , tfunc "pf6" pf6
             ("def hen(x, y, z):\n" ++
              "    return x + y + z + (7 if x < y else 16)")
           , tfunc "pf7" pf7
             ("def fact(n):\n" ++
              "    return 1 if n == 0 else n * fact(n - 1)")
           , tfunc "pf8" pf8 ("def glob(x, y, z):\n" ++
                            "    return x + y + z")
           , tfunc "pf9" pf9 ("def hack(x, y, z):\n" ++
                            "    return x - (y - z)")
           , tfunc "pf10" pf10 ("def icarus(x, y, z):\n" ++
                              "    return x - y - z")
           , tfunc "pf11" pf11 ("def jessie(x, y, z):\n" ++
                              "    return x - y + z")
           , tfunc "pf12" pf12 ("def kicks(x, y, z):\n" ++
                              "    return x + (y - z)")
           , tfunc "pf13" pf13 ("def lazy(x, y, z):\n" ++
                              "    return x + y - z")
           , tfunc "pf14" pf14 ("def mental(x, y, z):\n" ++
                              "    return x - (y + z)")
           , texpr "pe1" (EList sixSeven) "li(6, 7)"
           ]

runU :: IO ()
runU = utestloop tests