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

import Test.HUnit

import Data.Number.Sifflet
import Language.Sifflet.Expr (Expr(..), Function)
import Language.Sifflet.Export.Haskell
import Language.Sifflet.Export.ToHaskell

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

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

hsdef :: Function -> Decl
hsdef = functionToHsDecl


hf1, hf2, hf3, hf4, hf5, hf6, hf7, hf8, hf9 :: Decl

hf1 = hsdef f1
hf2 = hsdef f2
hf3 = hsdef f3
hf4 = hsdef f4
hf5 = hsdef f5
hf6 = hsdef f6
hf7 = hsdef f7
hf8 = hsdef f8
hf9 = hsdef f9

hf10, hf11, hf12, hf13, hf14 :: Decl

hf10 = hsdef f10
hf11 = hsdef f11
hf12 = hsdef f12
hf13 = hsdef f13
hf14 = hsdef f14


hf15, hf16 :: Decl

hf15 = hsdef f15
hf16 = hsdef f16

tests :: Test
tests = 
    let -- toHs = hsPretty -- was: pretty . alterParens bestParens
        tfunc label func result =
            assertEqual label result (hsPretty func)
        texpr label expr result =
            assertEqual label result (hsPretty (exprToHsExpr expr))
        sixSeven = map (ENumber . Exact) [6, 7]
    in assertAll
           [
            tfunc "hf1" hf1 ("foo =\n" ++
                           "    1")
           , tfunc "hf2" hf2 ("bar a b c =\n" ++
                            "    a * b + c * 2")
           , tfunc "hf3" hf3 ("cup a b c =\n" ++
                            "    (a + b) * (c + 2)")
           , tfunc "hf4" hf4 ("dook a b c =\n" ++
                            "    a + b * c")

           , tfunc "hf5" hf5 
             ("egg x y z =\n" ++
              "    x + y + if x < y then z + 7 else 1 + z * z")
           , tfunc "hf6" hf6
             ("hen x y z =\n" ++
              "    x + y + z + if x < y then 7 else 16")
           , tfunc "hf7" hf7
             ("fact n =\n" ++
              "    if n == 0 then 1 else n * fact (n - 1)")
           , tfunc "hf8" hf8 ("glob x y z =\n" ++
                              "    x + y + z")
           , tfunc "hf9" hf9 ("hack x y z =\n" ++
                              "    x - (y - z)")
           , tfunc "hf10" hf10 ("icarus x y z =\n" ++
                                "    x - y - z")
           , tfunc "hf11" hf11 ("jessie x y z =\n" ++
                                "    x - y + z")
           , tfunc "hf12" hf12 ("kicks x y z =\n" ++
                                "    x + (y - z)")
           , tfunc "hf13" hf13 ("lazy x y z =\n" ++
                                "    x + y - z")
           , tfunc "hf14" hf14 ("mental x y z =\n" ++
                                "    x - (y + z)")
           , tfunc "hf15" hf15 ("cons3 x y z =\n" ++
                                "    x : y : z : []")
           , tfunc "hf16" hf16 ("add_cons x y z =\n" ++
                                "    x + y : z : []")
           , texpr "e1" (EList sixSeven) "[6, 7]"
           ]

runU :: IO ()
runU = utestloop tests