diff --git a/README.md b/README.md index 4732ba0..3e97677 100644 --- a/README.md +++ b/README.md @@ -16,6 +16,8 @@ I have preserved all the original comments in the test. New comments are marked Since it is a not-mini compilation of Haskell code, I use cabal to manage the project. +### Tests Before 2024 + Run `cabal repl` in the root directory, it will open up a GHCi REPL that already loads the files for the tests. You can then load the modules for each year according to the following table to explore and test the functions. Note that simply running `ghci` and load the modules manually may not work because of the dependencies. Otherwise if you have not installed `cabal`, you can just copy the solution of any given year into a standalone Haskell file (remember to remove the `Year20XX.` prefix in the imports as well as the `tester` function). It should compile. @@ -33,3 +35,11 @@ If there's any issue or doubt on running the solutions, you are more than welcom | 2016 | `:m Test Year2016.Exam` | | 2015 | `:m Test Year2015.Exam` | | 2014 | `:m Test Year2014.Exam` | + +### Tests Since 2024 + +The tests since 2024 are presented in a different format. They are now in the form of a cabal package, and each test has its own cabal package. I have copied the original packages into the repo under folders "Year20XX". To interact with them, run `cabal repl` either in the root directory or in the folder of the test you want to explore. Then you can load the modules and test the functions as usual. + +## Test Suite + +Run `cabal test all` to run the test suites. The test suites before 2024 are made by myself, while later Haskell tests have their own test suites. diff --git a/cabal.project b/cabal.project new file mode 100644 index 0000000..217306e --- /dev/null +++ b/cabal.project @@ -0,0 +1,4 @@ +packages: + . + src/Year2024/ +tests: True diff --git a/doc-jan-haskell.cabal b/doc-jan-haskell.cabal index bd9a2dd..d72c2f8 100644 --- a/doc-jan-haskell.cabal +++ b/doc-jan-haskell.cabal @@ -78,6 +78,7 @@ test-suite test build-depends: base, containers, + hft, mtl, text, transformers, diff --git a/src/Year2024/hft.cabal b/src/Year2024/hft.cabal new file mode 100644 index 0000000..e4017f2 --- /dev/null +++ b/src/Year2024/hft.cabal @@ -0,0 +1,25 @@ +cabal-version: 3.0 +-- WARNING: YOU MUST NOT UNDER ANY CIRCUMSTANCES EDIT THIS FILE, YOU HAVE BEEN WARNED +name: hft +version: 0.1.0.0 +synopsis: Haskell Final Test 23/24 +author: Imperial College London +maintainer: j.willis19@imperial.ac.uk +build-type: Simple + +library + exposed-modules: Int, Types, Utilities, Examples + hs-source-dirs: src + default-language: Haskell2010 + build-depends: base >=4.13 && <5, + containers + +test-suite hft-test + type: exitcode-stdio-1.0 + hs-source-dirs: test + default-language: Haskell2010 + other-modules: IC.TestSuite + main-is: Tests.hs + ghc-options: -threaded + build-depends: hft, + base >=4.13 && <5 diff --git a/src/Year2024/src/Examples.hs b/src/Year2024/src/Examples.hs new file mode 100644 index 0000000..ede63bb --- /dev/null +++ b/src/Year2024/src/Examples.hs @@ -0,0 +1,68 @@ +module Examples where + +import Types +import Data.Ratio ((%)) + +p1, p2, p3, p4, p5 :: Polynomial +p1 = [(5,0)] +p2 = [(1,1)] +p3 = [(2,2),(-3,1),(1,0)] +p4 = [(4,1),(-3,0)] +p5 = [(2,3),(-2,1),(2,0)] + +x :: Expr +x = P [(1,1)] + +-- Basic polynomials +e1, e2, e3, e4, e5 :: Expr +e1 = P p1 +e2 = P p2 +e3 = P p3 +e4 = P p4 +e5 = P p5 + +-- Addition of polynomials +e6 :: Expr +e6 = Add e3 e5 + +-- Multiplication by constant +e7 :: Expr +e7 = Mul e1 e6 + +-- Simple functions of x +e8, e9 :: Expr +e8 = Log e2 +e9 = Pow e2 (-1) + +-- Inverse chain rule, id +e10, e11 :: Expr +e10 = Mul e4 e3 +e11 = Mul (Pow x (-1)) (Log x) + +-- Inverse chain rule, others +e12, e13 :: Expr +e12 = Mul e4 (Log e3) +e13 = Mul (Pow e3 (3/2)) e4 + +-- Now with a constant factor +e14, e15 :: Expr +e14 = Mul e4 (Pow (Mul e1 e3) (3/2)) +e15 = Mul (P [(1,2), (-1,0)]) (Log (P [(1,3), (-3,1)])) + +-- No integral to be found +e16 :: Expr +e16 = Mul (Log e3) (Pow e4 (1/2)) + +-- Secret testing... +e17, e18, e19, e20, e21, e22 :: Expr +e17 = + Mul (P [(4 % 5,1),((-3) % 5,0)]) (Pow (Mul (P [(5 % 1,0)]) (P [(2 % 1,2),((-3) % 1,1),(1 % 1,0)])) (3 % 2)) +e18 = + Mul (P [(1 % 5,2),((-1) % 5,0)]) (Log (P [(1 % 1,3),((-3) % 1,1)])) +-- d/dx has factor of 3 => multiply by 1/3 +e19 = P [(1,2), (-1,0)] +e20 = P [(1,3), (-3,1)] +e21 = Mul e19 (Log e20) + +-- As above but making 5/3 +e22 = Mul (Mul e1 e19) (Log e20) diff --git a/src/Year2024/src/Int.hs b/src/Year2024/src/Int.hs new file mode 100644 index 0000000..2dc2598 --- /dev/null +++ b/src/Year2024/src/Int.hs @@ -0,0 +1,130 @@ +{-# LANGUAGE NegativeLiterals #-} +{-# LANGUAGE ViewPatterns #-} + +module Int where + +import GHC.Real +import Data.List +import Data.Maybe +import Control.Applicative + +import Types +import Utilities +import Examples + +import Data.Bifunctor + +-- +-- Universal assumptions/preconditions: +-- 1. All polynomials are in standard form with decreasing +-- powers of x +-- 2. 0 is represented by P [(0, 0)]; P [] is undefined for +-- the purposes of the exercise. +-- 3. All constants will be polynomials of the form +-- [(c, 0)], e.g. logarithms of constants and constant +-- powers will not appear. +-- 4. All computed integrals omit the constant of integration. +-- + +------------------------------------------------- +-- Part I (13 marks) + +addP :: Polynomial -> Polynomial -> Polynomial +addP p1@((c1,e1):r1) p2@((c2,e2):r2) + | e1 > e2 = (c1, e1) : addP r1 p2 + | e1 < e2 = (c2, e2) : addP p1 r2 + | otherwise = (c1 + c2, e1) : addP r1 r2 +addP p1 p2 = p1 ++ p2 -- one of them is empty + +mulP :: Polynomial -> Polynomial -> Polynomial +mulP p = sumP . map (\(c,e) -> map (bimap (c *) (e +)) p) + +sumP :: [Polynomial] -> Polynomial +sumP = foldl' addP [(0, 0)] + +prodP :: [Polynomial] -> Polynomial +prodP = foldl' mulP [(1, 0)] + +diffT :: Term -> Term +diffT (c, 0) = (0, 0) +diffT (c, e) = (c * (e % 1), e - 1) + +-- > The speƧ should specify the constant term to be zero! +intT :: Term -> Term +intT (0, 0) = (0, 0) +intT (c, e) = (c / (e % 1 + 1), e + 1) + +diffP :: Polynomial -> Polynomial +diffP = map diffT + +intP :: Polynomial -> Polynomial +intP = map intT + +------------------------------------------------- +-- Part II (7 marks) + +diffE :: Expr -> Expr +diffE (P p) = P $ diffP p +diffE (Add e1 e2) = Add (diffE e1) (diffE e2) +diffE (Mul e1 e2) = Add (Mul (diffE e1) e2) (Mul e1 (diffE e2)) +diffE (Pow e n) = Mul (Mul (P [(n, 0)]) (Pow e (n - 1))) (diffE e) +diffE (Log e) = Mul (Pow e (-1)) (diffE e) + +-- +-- Given +-- +toExpr :: Rational -> Expr +toExpr n = P [(n, 0)] + +isConstant :: Expr -> Bool +isConstant (P [(_, 0)]) = True +isConstant _ = False + +simplifiedDiff :: Expr -> Expr +simplifiedDiff = simplify . diffE + +printDiff :: Expr -> IO () +printDiff = prettyPrint . simplifiedDiff + +------------------------------------------------- +-- Part III (10 marks) + +intE :: Expr -> Maybe Expr +intE (P p) = Just $ P (intP p) +intE (Add e1 e2) = Add <$> intE e1 <*> intE e2 +intE (Mul e1 e2) + | isConstant e1 = Mul e1 <$> intE e2 + | isConstant e2 = Mul e2 <$> intE e1 + | otherwise = applyICR e1 e2 <|> applyICR e2 e1 +intE e = applyICR e (toExpr 1) + +applyICR :: Expr -> Expr -> Maybe Expr +applyICR fg g' = case factorise g' (diffE fg) of + Just coeff -> Just $ Mul (toExpr $ coeff / 2) (Pow fg 2) + Nothing -> case fg of + Pow g n -> do + coeff <- factorise g' (diffE g) + pure $ case n of + -1 -> Mul (toExpr coeff) (Log g) + _ -> Mul (toExpr $ coeff / (n + 1)) (Pow g (n + 1)) + Log g -> do + coeff <- factorise g' (diffE g) + pure $ Mul (toExpr coeff) (Mul g (Add (Log g) (toExpr -1))) + _ -> Nothing + where + splitByCoeff (simplify -> e) = case e of + P [(c, 0)] -> (c, toExpr 1) + Mul (P [(c, 0)]) e' -> (c, e') + _ -> (1, e) + factorise (splitByCoeff -> (c1, r1)) (splitByCoeff -> (c2, r2)) + | r1 == r2 = Just $ c1 / c2 + | otherwise = Nothing + +-- +-- Given... +-- +simplifiedInt :: Expr -> Maybe Expr +simplifiedInt = fmap simplify . intE + +printInt :: Expr -> IO () +printInt e = maybe (putStrLn "Fail") prettyPrint (simplifiedInt e) diff --git a/src/Year2024/src/Types.hs b/src/Year2024/src/Types.hs new file mode 100644 index 0000000..dd512de --- /dev/null +++ b/src/Year2024/src/Types.hs @@ -0,0 +1,15 @@ +module Types where + +-- WARNING: DO NOT EDIT THIS FILE FOR *ANY* REASON, ANY CHANGES WILL BE DISCARDED +-- YOU WILL BE PENALISED IF YOU CODE NO LONGER COMPILES. + +type Coefficient = Rational +type Exponent = Integer +type Term = (Coefficient, Exponent) +type Polynomial = [Term] +data Expr = P Polynomial + | Add Expr Expr + | Mul Expr Expr + | Pow Expr Rational + | Log Expr + deriving (Eq, Ord, Show) diff --git a/src/Year2024/src/Utilities.hs b/src/Year2024/src/Utilities.hs new file mode 100644 index 0000000..e7f8091 --- /dev/null +++ b/src/Year2024/src/Utilities.hs @@ -0,0 +1,182 @@ +{-# LANGUAGE FlexibleInstances, OverloadedStrings #-} +module Utilities (Pretty(pretty, prettyPrint), simplify) where + +-- WARNING: DO NOT EDIT THIS FILE FOR *ANY* REASON, ANY CHANGES WILL BE DISCARDED +-- YOU WILL BE PENALISED IF YOU CODE NO LONGER COMPILES. + +-- You're NOT advised to spend any time dwelling on this file. The functions +-- pretty, prettyPrint, and simplify are explained in the spec, the +-- implementations are unimportant and obtuse. + +import Prelude hiding (gcd) +import GHC.Real (Ratio((:%)), (%)) +import Data.List (groupBy, sort, sortOn) +import Data.Ord (Down(Down)) +import Data.Function (on) +import Data.String (IsString(..)) + +import Types + +instance IsString (String -> String) where + fromString = (++) + +class Pretty a where + -- this allows for an asymptotically more efficient pretty printing + prettys :: a -> String -> String + pretty :: a -> String + pretty x = prettys x [] + prettyPrint :: a -> IO () + prettyPrint = putStrLn . pretty + +instance Pretty Rational where + prettys (a :% 1) = shows a + prettys (a :% b) + | a < 0 = "(-" . shows (abs a) . "/" . shows b . ")" + | otherwise = "(" . shows a . "/" . shows b . ")" + +instance Pretty Polynomial where + prettys p = "[" . (foldr1 pm (map pretty p) ++) . "]" + -- cannot difference list this, because of the need to + -- inspect the head character, unfortunately + where pm s1 ('-' : s) = s1 ++ " - " ++ s + pm s1 "" = s1 + pm "" s = s + pm s1 s = s1 ++ " + " ++ s + prettyPrint p + | null p' = putStrLn "[0]" + | otherwise = putStrLn (pretty p') + where p' = filter ((/= 0) . fst) p + +instance Pretty Expr where + prettys (P p) = prettys p + prettys (Add e e') = prettys e + . if c == '-' then " - " . (s' ++) else " + " . (s ++) + where s@(c : s') = pretty e' + prettys (Mul e e') = prettys' e . " . " . prettys' e' + where prettys' e@(Add _ _) = "(" . prettys e . ")" + prettys' e = prettys e + prettys (Pow e@(P [_]) n) = prettys e . "^" . prettys n + prettys (Pow e n) = "(" . prettys e . ")^" . prettys n + prettys (Log e@(P p)) = "log" . prettys e + prettys (Log e) = "log (" . prettys e . ")" + +instance Pretty Term where + prettys (a, 0) = prettys a + prettys (1 :% 1, n) = prettysPow n + prettys (-1 :% 1, n) = "-" . prettysPow n + prettys (a@(0 :% _), n) | n > 0 = "" + prettys (a, n) = prettys a . prettysPow n + +prettysPow :: Integer -> (String -> String) +prettysPow n + | n < 2 = (replicate (fromInteger n) 'x' ++) + | otherwise = "x^" . shows n + +-------------------------- +toExpr :: Rational -> Expr +toExpr n = P [(n, 0)] + +isConstant :: Expr -> Bool +isConstant (P [(_, 0)]) = True +isConstant _ = False + +isZero :: Expr -> Bool +isZero (P [(0, 0)]) = True +isZero _ = False + +isOne :: Expr -> Bool +isOne (P [(1, 0)]) = True +isOne _ = False + +gcd :: Rational -> Rational -> Rational +gcd r r' = gcd' (abs r) (abs r') + where gcd' 0 r' = r' + gcd' r 0 = r + gcd' r r' = gcd' mn (mx - mn) + where [mn, mx] = sort [r,r'] + +simplify :: Expr -> Expr +simplify = simplify' . factorise . simplify' + +factorise :: Expr -> Expr +factorise e@(P p) = factor e +factorise (Add e e') = Add e1 e2 + where [e1, e2] = sort' [factorise e, factorise e'] +factorise (Mul e e') = Mul e1 e2 + where [e1, e2] = sort' [factorise e, factorise e'] +factorise (Pow e n) = Pow (factorise e) n +factorise (Log e) = Log (factorise e) + +sort' :: [Expr] -> [Expr] +sort' ps@[P p, P p'] + | less p p' = ps + | otherwise = [P p', P p] +sort' ps = sort ps + +less :: [Term] -> [Term] -> Bool +less ((c, e) : ps) ((c', e') : ps') = e <= e' && less ps ps' +less [] _ = True +less _ [] = False + +factor :: Expr -> Expr +factor e@(P [(0, 0)]) = e +factor e@(P ts) + | length ts' < 2 = P ts' + | g == 1 = P ts' + | otherwise = Mul (toExpr g) (P [(c / g, n) | (c, n) <- ts']) + where g = foldr1 gcd (map fst ts') + ts' = filter (/=(0,0)) ts +factor e = e + +simplify':: Expr -> Expr +simplify' (Add e e') = simplify'' (Add (simplify' e) (simplify' e')) +simplify' (Mul e e') = simplify'' (Mul (simplify' e) (simplify' e')) +simplify' (Pow e n) = simplify'' (Pow (simplify' e) n) +simplify' (Log e) = simplify'' (Log (simplify' e)) +simplify' e = e + +normalise :: Polynomial -> Polynomial +normalise = map collapse . groupBy ((==) `on` snd) . sortOn (Down . snd) + where collapse ts@((_, expo):_) = (sum (map fst ts), expo) + +crs p1 p2 = normalise (biliftA2 (*) (+) <$> p1 <*> p2) + +simplify'' :: Expr -> Expr +simplify'' (Add (P p1) (P p2)) = P (normalise (p1 ++ p2)) +simplify'' (Add e e') + | isZero e = e' + | isZero e' = e +simplify'' (Add (Mul e1 e2) (Mul e1' e2')) + | isConstant e1, isConstant e1', e2 == e2' = Mul (simplify'' (Add e1 e1')) e2 +simplify'' (Add (Log e) (Log e')) = Log (simplify'' (Mul e e')) +simplify'' (Mul e e') + | isOne e = e' + | isOne e' = e + | isZero e = toExpr 0 + | isZero e' = toExpr 0 +simplify'' (Mul e@(P p1) (P p2)) + | not (isConstant e) = P (crs p1 p2) +simplify'' (Mul e1 (Mul e2 e3)) + | isConstant e1 + , isConstant e2 = simplify'' (Mul (P (crs (unP e1) (unP e2))) e3) + | isConstant e2 = Mul e2 (simplify'' (Mul e1 e3)) +simplify'' (Pow e (0 :% 1)) = toExpr 1 +simplify'' (Pow e (1 :% 1)) = e +simplify'' (Pow (P p) (n :% 1)) + | n > 0 = P (foldr1 crs (replicate (fromInteger n) p)) +simplify'' (Mul e (Pow e' n)) + | e == e' = Pow e' (n + 1) +simplify'' (Mul (P [(c, m)]) (Pow e'@(P [(c', 1)]) n)) = + Mul (P [(c * c', 0)]) (Pow (P [(1, 1)]) (m % 1 + n)) +simplify'' (Mul (Pow e m) (Pow e' n)) + | e == e' = Pow e (m + n) + | m == n = Pow (Mul e e') m +simplify'' (Log (Pow e n)) = Mul (toExpr n) (Log e) +simplify'' e = e + +unP :: Expr -> Polynomial +unP (P p) = p +unP e = [] + +biliftA2 :: (a -> b -> c) -> (x -> y -> z) -> (a, x) -> (b, y) -> (c, z) +biliftA2 f g (u, v) (x, y) = (f u x, g v y) diff --git a/src/Year2024/test/IC/TestSuite.hs b/src/Year2024/test/IC/TestSuite.hs new file mode 100644 index 0000000..969c600 --- /dev/null +++ b/src/Year2024/test/IC/TestSuite.hs @@ -0,0 +1,83 @@ +{-# LANGUAGE ExistentialQuantification #-} +module IC.TestSuite (TestGroup, TestCase, testGroup, runTests, (-->)) where + +import Control.Exception ( evaluate, SomeException, handle + , ErrorCall(..), fromException) +import Control.Monad (forM) +import Data.Functor (($>)) +import Data.List (foldl') +import GHC.Stack ( HasCallStack, callStack, getCallStack + , SrcLoc(srcLocFile, srcLocStartLine) ) +import System.Exit (exitFailure, exitSuccess) +import System.Timeout (timeout) + +data TestGroup = TestGroup !String ![TestCase] +data TestCase = forall a. (HasCallStack, Eq a, Show a) => TestCase a !a + +testGroup :: String -> [TestCase] -> TestGroup +testGroup = TestGroup + +runTests :: [TestGroup] -> IO () +runTests tests = do + allPass <- fmap and (mapM goTest tests) + if allPass then exitSuccess + else exitFailure + +goTest :: TestGroup -> IO Bool +goTest (TestGroup name cases) = do + counts <- forM cases (handle majorExceptionHandler . goTestOne name) + let passes = filter id counts + putStrLn $ name ++ ": " ++ show (length passes) + ++ " / " ++ show (length counts) + putStrLn "" + return $ length passes == length counts + where + majorExceptionHandler :: SomeException -> IO Bool + majorExceptionHandler e = + putStrLn ("Argument exception: " ++ show e) $> False + +-- this is irrefutable to remind us we don't want to evaluate before being under +-- the exception handler! +goTestOne :: [Char] -> TestCase -> IO Bool +goTestOne name (TestCase ~actual expected) = handle exceptionHandler $ do + r <- timeout (10^6) $ if actual == expected then return True + else failedStanza Nothing + handleTimeout r + where + failedStanza :: Maybe SomeException -> IO Bool + failedStanza e = do + putStrLn . unlines $ + [ " Failure in " ++ name ++ sourceLoc ++ ":" + , " expected: " ++ show expected + , " but got: " ++ maybe (show actual) clean e] + return False + + handleTimeout :: Maybe Bool -> IO Bool + handleTimeout Nothing = + do putStrLn (" Timeout in " ++ name ++ sourceLoc) + return False + handleTimeout (Just r) = return r + + sourceLoc :: HasCallStack => String + sourceLoc = maybe "" (showSrcLoc . snd) (lastMaybe (getCallStack callStack)) + where showSrcLoc loc = + " (" ++ srcLocFile loc ++ ":" ++ show (srcLocStartLine loc) ++ ")" + + exceptionHandler :: SomeException -> IO Bool + exceptionHandler = failedStanza . Just + + clean :: SomeException -> String + clean e + | Just (ErrorCallWithLocation msg trace) <- fromException e = + -- the last line of the trace is the student's code (they won't add + -- HasCallStack, so only one line will count): this is indented by 2 + -- characters, so trim one and use the other as the space between from. + msg ++ " (from" ++ tail (last (lines trace)) ++ ")" + | otherwise = show e + +infix 0 --> +(-->) :: (HasCallStack, Eq a, Show a) => a -> a -> TestCase +(-->) = TestCase + +lastMaybe :: [a] -> Maybe a +lastMaybe = foldl' (const Just) Nothing diff --git a/src/Year2024/test/Tests.hs b/src/Year2024/test/Tests.hs new file mode 100644 index 0000000..a1f7cea --- /dev/null +++ b/src/Year2024/test/Tests.hs @@ -0,0 +1,123 @@ +import IC.TestSuite + +import Int +import Utilities +import Examples +import Types + +main :: IO () +main = runTests tests + +tests :: [TestGroup] +tests = + [ testGroup "addP" addPTests + , testGroup "mulP" mulPTests + , testGroup "sumP" sumPTests + , testGroup "prodP" prodPTests + , testGroup "diffT" diffTTests + , testGroup "intT" intTTests + , testGroup "diffP" diffPTests + , testGroup "intP" intPTests + -- PART II + , testGroup "diffE" diffETests + -- PART III + , testGroup "intE" intETests + , testGroup "intESecret" intESecretTests + ] + +addPTests :: [TestCase] +addPTests = [ pretty (addP p2 p2) --> "[2x]" + , pretty (addP p3 p4) --> "[2x^2 + x - 2]" + , pretty (addP p5 [(0, 0)]) --> "[2x^3 - 2x + 2]" + , pretty (addP [(3, 2)] [(1, 1)]) --> "[3x^2 + x]" + ] + +mulPTests :: [TestCase] +mulPTests = [ pretty (mulP p3 p4) --> "[8x^3 - 18x^2 + 13x - 3]" + ] + +sumPTests :: [TestCase] +sumPTests = [ pretty (sumP [[(0, 0)]]) --> "[0]" + , pretty (sumP [p1, p2, p3, p4, p5]) --> "[2x^3 + 2x^2 + 5]" + ] + +prodPTests :: [TestCase] +prodPTests = [ pretty (prodP [p3, p5]) --> + "[4x^5 - 6x^4 - 2x^3 + 10x^2 - 8x + 2]" + ] + +diffTTests :: [TestCase] +diffTTests = [ diffT (1, 0) --> (0, 0) + , diffT (2, 3) --> (6, 2) + ] + +intTTests :: [TestCase] +intTTests = [ intT (1, 0) --> (1, 1) + , intT (2, 3) --> (1 / 2, 4) + ] + +diffPTests :: [TestCase] +diffPTests = [ pretty (simplify (P (diffP p3))) --> + -- without the `simplify . P`, this needs a `+ 0` on the end + "[4x - 3]" + ] + +intPTests :: [TestCase] +intPTests = [ pretty (intP p3) --> "[(2/3)x^3 + (-3/2)x^2 + x]" + ] + +diffETests :: [TestCase] +diffETests = [ pretty (simplifiedDiff e3) --> "[4x - 3]" + , pretty (simplifiedDiff e10) --> "[24x^2 - 36x + 13]" + , pretty (simplifiedDiff e11) --> "[-1] . [x]^-2 . log[x] + [x]^-2" + ] + +intETests :: [TestCase] +intETests = [ fmap pretty (simplifiedInt e1) --> + Just "[5x]" + , fmap pretty (simplifiedInt e2) --> + Just "[(1/2)x^2]" + , fmap pretty (simplifiedInt e3) --> + Just "[(1/6)] . [4x^3 - 9x^2 + 6x]" + , fmap pretty (simplifiedInt e4) --> + Just "[2x^2 - 3x]" + , fmap pretty (simplifiedInt e5) --> + Just "[(1/2)] . [x^4 - 2x^2 + 4x]" + , fmap pretty (simplifiedInt e6) --> + Just "[(1/6)] . [3x^4 + 4x^3 - 15x^2 + 18x]" + , fmap pretty (simplifiedInt e7) --> + Just "[(5/6)] . [3x^4 + 4x^3 - 15x^2 + 18x]" + , fmap pretty (simplifiedInt e8) --> + Just "[x] . ([-1] + log[x])" + , fmap pretty (simplifiedInt e9) --> + Just "log[x]" + , fmap pretty (simplifiedInt e10) --> + Just "[(1/2)] . [4x^4 - 12x^3 + 13x^2 - 6x + 1]" + , fmap pretty (simplifiedInt e11) --> + Just "[(1/2)] . (log[x])^2" + , fmap pretty (simplifiedInt e12) --> + Just "[2x^2 - 3x + 1] . ([-1] + log[2x^2 - 3x + 1])" + , fmap pretty (simplifiedInt e13) --> + Just "[(2/5)] . ([2x^2 - 3x + 1])^(5/2)" + , fmap pretty (simplifiedInt e14) --> + Just "[(2/25)] . ([5] . [2x^2 - 3x + 1])^(5/2)" + , fmap pretty (simplifiedInt e15) --> + Just "[(1/3)] . [x^3 - 3x] . ([-1] + log[x^3 - 3x])" + , fmap pretty (simplifiedInt e16) --> + Nothing + ] + +intESecretTests :: [TestCase] +intESecretTests = [ fmap pretty (simplifiedInt e17) --> + Just "[(2/125)] . ([5] . [2x^2 - 3x + 1])^(5/2)" + , fmap pretty (simplifiedInt e18) --> + Just "[(1/15)] . [x^3 - 3x] . ([-1] + log[x^3 - 3x])" + , fmap pretty (simplifiedInt e19) --> + Just "[(1/3)] . [x^3 - 3x]" + , fmap pretty (simplifiedInt e20) --> + Just "[(1/4)] . [x^4 - 6x^2]" + , fmap pretty (simplifiedInt e21) --> + Just "[(1/3)] . [x^3 - 3x] . ([-1] + log[x^3 - 3x])" + , fmap pretty (simplifiedInt e22) --> + Just "[(5/3)] . [x^3 - 3x] . ([-1] + log[x^3 - 3x])" + ]