Skip to content

Commit

Permalink
Add comments for 2024
Browse files Browse the repository at this point in the history
  • Loading branch information
MMZK1526 committed Feb 2, 2024
1 parent f92be15 commit 7600fc9
Show file tree
Hide file tree
Showing 2 changed files with 25 additions and 10 deletions.
2 changes: 1 addition & 1 deletion README.md
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ If there's any issue or doubt on running the solutions, you are more than welcom

### 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.
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 (written by Jamie Willis). 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

Expand Down
33 changes: 24 additions & 9 deletions src/Year2024/src/Int.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,18 @@
{-# LANGUAGE NegativeLiterals #-}
{-# LANGUAGE ViewPatterns #-}

-- > This test can be considered as a continuation of a previous tutorial on
-- > differentiation. Of course, integration in general is not as
-- > straightforward. The test only focuses on one major technique, namely the
-- > reverse chain rule.
-- >
-- > In my opinion, this test is not difficult, but there are many edge cases
-- > and it is very easy to miss out on some of them, espcially under time
-- > pressure.
-- >
-- > In practice, of course, the integration rules covered in the test is only
-- > a tiny fraction, and it is in general a very hard problem to solve.

module Int where

import GHC.Real
Expand Down Expand Up @@ -34,7 +46,7 @@ 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
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)
Expand Down Expand Up @@ -95,27 +107,30 @@ 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)
| otherwise = applyICR e1 e2 <|> applyICR e2 e1 -- > try both ways
intE e = applyICR e (toExpr 1) -- > the multiply-by-one trick

applyICR :: Expr -> Expr -> Maybe Expr
applyICR fg g' = case factorise g' (diffE fg) of
applyICR fg g' = case factorise g' (diffE fg) of -- > Try the case "f(x)f'(x)"
Just coeff -> Just $ Mul (toExpr $ coeff / 2) (Pow fg 2)
Nothing -> case fg of
Pow g n -> do
coeff <- factorise g' (diffE g)
coeff <- factorise g' (diffE g) -- > Try the case "g^n(x)g'(x)"
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)
coeff <- factorise g' (diffE g) -- > Try the case "log(g(x))g'(x)"
pure $ Mul (toExpr coeff) (Mul g (Add (Log g) (toExpr -1)))
_ -> Nothing
where
-- > split a function into a coefficient times the simplified form.
splitByCoeff (simplify -> e) = case e of
P [(c, 0)] -> (c, toExpr 1)
Mul (P [(c, 0)]) e' -> (c, e')
_ -> (1, e)
P [(c, 0)] -> (c, toExpr 1) -- > f(x) = c => (c, 1)
Mul (P [(c, 0)]) e' -> (c, e') -- > f(x) = c * g(x) => (c, g(x))
_ -> (1, e) -- > f(x) can't be simplified => (1, f(x))
-- > attempt to factorise the given functions, which only works if they
-- > can both be split into a coefficient times the same simplified form.
factorise (splitByCoeff -> (c1, r1)) (splitByCoeff -> (c2, r2))
| r1 == r2 = Just $ c1 / c2
| otherwise = Nothing
Expand Down

0 comments on commit 7600fc9

Please sign in to comment.