Skip to content

Commit de6361c

Browse files
committed
Need to switch branch briefly
1 parent 8784a11 commit de6361c

File tree

7 files changed

+144
-81
lines changed

7 files changed

+144
-81
lines changed

Book/build.py

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -109,6 +109,7 @@ def build_index(sources):
109109
("Differential calculus", "Physics/src/Calculus/DifferentialCalc.lhs"),
110110
("Integral calculus", "Physics/src/Calculus/IntegralCalc.lhs"),
111111
("Plotting graphs", "Physics/src/Calculus/VisVerApp.lhs"),
112+
("Syntax trees", "Physics/src/Calculus/SyntaxTree.lhs"),
112113
]),
113114
("Linear algebra", [
114115
("Vectors", "Physics/src/Vector/Vector.lhs")

Physics/app/Main.hs

Lines changed: 0 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,4 @@
11
module Main where
22

3-
import Vector.Vector
4-
import Calculus.Calculus
5-
6-
--import Lib
7-
83
main :: IO ()
94
main = undefined

Physics/src/Calculus/SyntaxTree.lhs

Lines changed: 66 additions & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,72 @@
11
> module Calculus.SyntaxTree where
22

3-
> import Calculus.Calculus as C
3+
> import Calculus.FunExpr
4+
> import Calculus.DifferentialCalc
5+
> import Calculus.IntegralCalc
6+
7+
A fun and useful way to visualize expressions is to model them as trees. In our
8+
case we want to model $FunExpr$ where the nodes and leaves will be our
9+
constructors.
10+
11+
In order to do this will import two packages, one for constructing trees and one
12+
for pretty printing them.
13+
414
> import Data.Tree as T
515
> import Data.Tree.Pretty as P
616

7-
Pretty prints expressions as trees
17+
Now we can construct the function that takes a FunExpr and builds a tree from it.
18+
Every node is a string representation of the constructor and a list of its
19+
sub trees (branches).
20+
21+
> makeTree :: FunExpr -> Tree String
22+
> makeTree (e1 :+ e2) = Node "+" [makeTree e1, makeTree e2]
23+
> makeTree (e1 :- e2) = Node "-" [makeTree e1, makeTree e2]
24+
> makeTree (e1 :* e2) = Node "*" [makeTree e1, makeTree e2]
25+
> makeTree (e1 :/ e2) = Node "Div" [makeTree e1, makeTree e2]
26+
> makeTree (e1 :^ e2) = Node "**" [makeTree e1, makeTree e2]
27+
> makeTree (e1 :. e2) = Node "o" [makeTree e1, makeTree e2]
28+
> makeTree (D e) = Node "d/dx" [makeTree e]
29+
> makeTree (Delta r e) = Node "Δ" [makeTree (Const r), makeTree e]
30+
> makeTree (I e) = Node "I" [makeTree e]
31+
> makeTree Id = Node "Id" []
32+
> makeTree Exp = Node "Exp" []
33+
> makeTree Log = Node "Log" []
34+
> makeTree Sin = Node "Sin" []
35+
> makeTree Cos = Node "Cos" []
36+
> makeTree Asin = Node "Asin" []
37+
> makeTree Acos = Node "Acos" []
38+
> makeTree (Const num) = Node (show num) [] --(show (floor num)) [] -- | Note the use of floor
39+
40+
Now we construct trees from our expressions but we still need to print them out.
41+
For this we'll use the function `drawVerticalTree` which does exactly what its
42+
name suggests. We can then construct a function to draw expressions.
843

944
> printExpr :: FunExpr -> IO ()
1045
> printExpr = putStrLn . drawVerticalTree . makeTree
1146

47+
Now let's construct a mildly complicated expression
48+
49+
> e = Delta 3 (Delta (negate 5) (I Acos) :. (Acos :* Exp))
50+
51+
And print it out.
52+
53+
< ghci > printExpr e
54+
< Δ
55+
< |
56+
< -----------
57+
< / \
58+
< 3 o
59+
< |
60+
< ----------
61+
< / \
62+
< Δ *
63+
< | |
64+
< ---- -----
65+
< / \ / \
66+
< -5 I Acos Exp
67+
< |
68+
< Acos
69+
1270
Pretty prints the steps taken when canonifying an expression
1371

1472
> prettyCan :: FunExpr -> IO ()
@@ -34,43 +92,21 @@ Pretty prints syntactic checking of equality
3492
> putStrLn $ drawVerticalForest [makeTree e1, makeTree e2]
3593
> let c1 = canonify e1
3694
> c2 = canonify e2
37-
> in if c1 == e1 && c2 == e2 then putStrLn "Can't simplify no more"
95+
> in if c1 == e1 && c2 == e2 then putStrLn "Can't simplify no more"
3896
> >> return False
3997
> else prettyEqual c1 c2
4098

4199
Syntactic checking of equality
42100

43101
> equal :: FunExpr -> FunExpr -> Bool
44-
> equal e1 e2 = case e1 == e2 of
45-
> True -> True
46-
> False -> let c1 = canonify e1
47-
> c2 = canonify e2
48-
> in case e1 == c1 && c2 == e2 of
49-
> True -> False
50-
> False -> equal c1 c2
102+
> equal e1 e2 = (e1 == e2) ||
103+
> (let c1 = canonify e1
104+
> c2 = canonify e2
105+
> in (not (e1 == c1 && c2 == e2) && equal c1 c2))
51106

52107
Parse an expression as a Tree of Strings
53108

54-
> makeTree :: FunExpr -> Tree String
55-
> makeTree (e1 :+ e2) = Node "+" [makeTree e1, makeTree e2]
56-
> makeTree (e1 :- e2) = Node "-" [makeTree e1, makeTree e2]
57-
> makeTree (e1 :* e2) = Node "*" [makeTree e1, makeTree e2]
58-
> makeTree (e1 :/ e2) = Node "Div" [makeTree e1, makeTree e2]
59-
> makeTree (e1 :^ e2) = Node "**" [makeTree e1, makeTree e2]
60-
> makeTree (e1 :. e2) = Node "o" [makeTree e1, makeTree e2]
61-
> makeTree (D e) = Node "d/dx" [makeTree e]
62-
> makeTree (Delta r e) = Node "Δ" [makeTree (Const r), makeTree e]
63-
> makeTree (I r e) = Node "I" [makeTree (Const r), makeTree e]
64-
> makeTree Id = Node "Id" []
65-
> makeTree Exp = Node "Exp" []
66-
> makeTree Log = Node "Log" []
67-
> makeTree Sin = Node "Sin" []
68-
> makeTree Cos = Node "Cos" []
69-
> makeTree Asin = Node "Asin" []
70-
> makeTree Acos = Node "Acos" []
71-
> makeTree (Const num) = Node (show (floor num)) [] -- | Note the use of floor
72-
73-
Of course this is all bit too verbose, but I'm keeping it that way until every
109+
Of course this is all bit too verbose, but I'm keeping it that way until every
74110
case is covered, Calculus is a bit of a black box for me right now
75111

76112
> canonify :: FunExpr -> FunExpr
@@ -175,5 +211,3 @@ Dummy expressions
175211
> e4 = (Const 1 :+ Const 2) :* (Const 3 :+ Const 4)
176212
> e5 = (Const 1 :+ Const 2) :* (Const 4 :+ Const 3)
177213
> e6 = Const 2 :+ Const 3 :* Const 8 :* Const 19
178-
> e7 = (Delta 3 ((Delta (0 - 5) (I 7 Acos)) :. (Acos :* Exp)))
179-

Physics/src/Dimensions/Quantity.lhs

Lines changed: 4 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@ Quantities
2828

2929
> import qualified Dimensions.ValueLevel as V
3030
> import Dimensions.TypeLevel as T
31-
> import Prelude as P hiding (length, div)
31+
> import Prelude as P hiding (length)
3232

3333
We'll now create a data type for quantities and combine dimensions on value-level and type-level. Just as before, a bunch of GHC-extensions are necessary.
3434

@@ -65,14 +65,7 @@ Let's get on to the actual data type declaration.
6565
> data Quantity (d :: T.Dim) (v :: *) where
6666
> ValQuantity :: V.Dim -> v -> Quantity d v
6767

68-
<<<<<<< HEAD
69-
> lift :: Quantity dim a -> a
70-
> lift (Quantity _ v) = v
71-
72-
`data Quantity` creates a *type constructor*. Which means it takes two *types* (of certain *kinds*) to create another *type* (of a certain *kind*). For comparsion, here's a *value constructor* which takes two *values* (of certain *types*) as input to create another *value* (of a certain *type*).
73-
=======
7468
That was sure a mouthful! Let's break it down. `data Quantity (d :: T.Dim) (v :: *)` creates the *type constructor* `Quantity`. A type constructor takes types to create another type. In this case, the type constructor `Quantity` takes a type `d` of *kind* `T.Dim` and a type `v` of *kind* `*` to create the type `Quantity d v`. Let's see it in action
75-
>>>>>>> master
7669

7770
< type ExampleType = Quantity T.Length Double
7871

@@ -305,7 +298,7 @@ We often use `Double` as the value holding type. Doing exact comparsions isn't a
305298
Testing if a quantity is zero is something which might be a common operation. So we define it here.
306299

307300
> isZero :: (Fractional v, Ord v) => Quantity d v -> Bool
308-
> isZero (ValQuantity _ v) = (abs v) < 0.001
301+
> isZero (ValQuantity _ v) = abs v < 0.001
309302

310303

311304
Arithmetic on quantities
@@ -361,10 +354,10 @@ We quickly realize a pattern, so let's generalize a bit.
361354
> qmap f (ValQuantity d1 v) = ValQuantity d1 (f v)
362355

363356
> qmap' :: (a -> b) -> Quantity dim a -> Quantity dim b
364-
> qmap' f (Quantity d v) = Quantity d (f v)
357+
> qmap' f (ValQuantity d v) = ValQuantity d (f v)
365358

366359
> qfold :: (a -> a -> b) -> Quantity dim a -> Quantity dim a -> Quantity dim b
367-
> qfold f (Quantity d v1) (Quantity _ v2) = Quantity d (f v1 v2)
360+
> qfold f (ValQuantity d v1) (ValQuantity _ v2) = ValQuantity d (f v1 v2)
368361

369362
> sinq, cosq, asinq, acosq, atanq, expq, logq :: (Floating v) =>
370363
> Quantity One v -> Quantity One v

Physics/src/Dimensions/Usage.lhs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -129,4 +129,4 @@ To wrap up, let's create a function to calculate the kinectic energy à la
129129
> Quantity Energy Double
130130
> kinecticEnergy m v = m *# v *# v /# two
131131
> where
132-
> two = 2.0 # one
132+
> two = 2.0 # one

Physics/src/Dimensions/ValueLevel.lhs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@ Value-level dimensions
1515
> , luminosity
1616
> , one
1717
> ) where
18-
>
18+
>
1919
> import Prelude hiding (length, div)
2020

2121
From the introduction, two things became apparanent:

Physics/src/NewtonianMechanics/SingleParticle.lhs

Lines changed: 71 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
> module NewtonianMechanics.SingleParticle where
22

3-
< import Calculus.SyntaxTree
3+
%< import Calculus.SyntaxTree
44

55
> import Test.QuickCheck
66

@@ -19,20 +19,16 @@ position in each dimension, x, y, and z. Since we've already defined vectors and
1919
mathmatical functions in previous chapters we won't spend any time on them here
2020
and instead just import those two modules.
2121

22-
> import Calculus
22+
> import Calculus.FunExpr
23+
> import Calculus.DifferentialCalc -- Maybe remove
24+
> import Calculus.IntegralCalc -- Maybe remove
2325
> import Vector.Vector as V
2426

25-
The mass of a particle is just a numerical value so we'll model it using
26-
doubles.
27-
28-
< type Mass = Double
29-
30-
\ignore{
27+
The mass of a particle is just a scalar value so we'll model it using
28+
$FunExpr$.
3129

3230
> type Mass = FunExpr
3331

34-
}
35-
3632
We combine the constructor for vectors in three dimensions with the function
3733
expressions defined in the chapter on mathmatical analysis. We'll call this new
3834
type `VectorE` to signify that it's a vector of expressions.
@@ -49,13 +45,13 @@ of function expressions. So our data type is simply:
4945

5046
So now we can create our particles! Let's try it out!
5147

52-
**TODO: IMPLEMENT NUM INSTANCE FOR FunExpr AND REWRITE**
48+
> particle :: Particle
49+
> particle = P (V3 (3 * Id * Id) (2 * Id) 1) 3
50+
51+
Let's see what happens when we run this in the interpreter.
5352

54-
```
55-
ghci > let particle = P (V3 (3 :* Id :* Id) (2 :* Id) 1) 3
56-
ghci > particle
57-
P {pos = (((3 * id) * id) x, (2 * id) y, 1 z), mass = 3}
58-
```
53+
< ghci > particle
54+
< P {pos = (((3 * id) * id) x, (2 * id) y, 1 z), mass = 3}
5955

6056
We've created our first particle! And as we can see from the print out it's
6157
accelerating by $3t^2$ in the x-dimension, has a constant velocity of $2
@@ -84,7 +80,15 @@ rather elegant way of computing the velocity of a particle.
8480
> velocity :: Particle -> VectorE
8581
> velocity = vmap D . pos
8682

87-
Acceleration is defined as the derivative of the velocity with respect to time,
83+
We can try this out in the interpreter with our newly created particle.
84+
85+
< ghci > velocity particle
86+
< ((D ((3 * id) * id)) x, (D (2 * id)) y, (D 1) z)
87+
88+
Not very readable but at least we can see that it correctly maps the derivative
89+
over the components of the vector.
90+
91+
*Acceleration* is defined as the derivative of the velocity with respect to time,
8892
or the second derivative of the position. More formally:
8993

9094
\begin{equation*}
@@ -140,6 +144,10 @@ mathematically defined as follows:
140144
\vec{F} = \frac{d \vec{p}}{d t} = \frac{d(m \cdot \vec{v})}{d t}
141145
\end{equation}
142146

147+
Force is a vector so let's create a type synonym to make this clearer.
148+
149+
> type Force = VectorE
150+
143151
The quantity $m \cdot \vec{v}$ is what we mean when we say momentum. So the law
144152
states that the net force on a particle is equal to the rate of change of the
145153
momentum with respect to time. And since the definition of acceleration is
@@ -153,12 +161,11 @@ namely:
153161
And thus if the particle is accelerating we can calculate the force that
154162
must be acting on it, in code this would be:
155163

156-
157-
< force :: Particle -> VectorE
158-
< force p = vmap (* m) a
159-
< where
160-
< m = mass p
161-
< a = acceleration p
164+
> force :: Particle -> Force
165+
> force p = vmap (* m) a
166+
> where
167+
> m = mass p
168+
> a = acceleration p
162169

163170
Where the acceleration of particle is found by deriving the velocity of that
164171
same particle with respect to $t$:
@@ -219,12 +226,45 @@ types.
219226
> v = velocity p
220227
> v2 = square v
221228

222-
Work and energy
223-
---------------------
229+
Potential energy
230+
-----------------
231+
232+
In classical mechanics potential energy is defined as the energy possed by a
233+
particle because of its position relative to other particles, its electrical
234+
charge and other factors. This means that to actually calculate the potential
235+
energy of a particle we'd have to take into account all other particles that
236+
populate the system no matter how far apart they are.
237+
238+
Potential energy near Earth
239+
------------------------------------
240+
241+
Thankfully if we're close to the Earths gravitational field it's ok
242+
to simplify this problem and only take into account the Earths gravitational
243+
pull since all other factors are negliable in comparison.
244+
245+
The potential energy for particles affected by gravity is defined with
246+
mathmatical notation as:
247+
248+
\begin{equation}
249+
E_p = m \cdot g \cdot h
250+
\end{equation}
251+
where $m$ is the mass of the particle, $h$ its height, and $g$ is the
252+
acceleration due to gravity (9.82 $m/s^2$).
253+
254+
> potentialEnergy :: Particle -> Energy
255+
> potentialEnergy p = m * g * h
256+
> where
257+
> m = mass p
258+
> g = Const 9.82
259+
> (V3 _ _ h) = pos p
260+
261+
Work
262+
----
224263

225264
If a constant force $\vec{F}$ is applied to a particle that moves from
226265
position $\vec{r_1}$ to $\vec{r_2}$ then the *work* done by the force is defined
227-
as the dot product of the force and the vector of displacement.
266+
as the dot product of the force and the vector of displacement. In mathmatical
267+
notation this is written as
228268

229269
\begin{equation}
230270
W = \vec{F} \cdot \Delta \vec{r}
@@ -309,8 +349,8 @@ magnitude of the vector, if the gravitational force originates from O. Hmmm
309349

310350
This seems weird since I don't know what the frame of reference is...
311351

312-
> potentialEnergy :: Particle -> Energy
313-
> potentialEnergy p = undefined
314-
> where
315-
> m = mass p
316-
> (V3 x _ _) = pos p
352+
< potentialEnergy :: Particle -> Energy
353+
< potentialEnergy p = undefined
354+
< where
355+
< m = mass p
356+
< (V3 x _ _) = pos p

0 commit comments

Comments
 (0)