Skip to content

Commit 1d0ed96

Browse files
author
Oskar Lundström
committed
Starade göra mer strukturerat på utökad Quantity
1 parent c8d8898 commit 1d0ed96

File tree

2 files changed

+233
-24
lines changed

2 files changed

+233
-24
lines changed

Physics/src/Dimensions/Quantity.lhs

Lines changed: 31 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -20,9 +20,10 @@ Quantities
2020
> , meter, kilogram, second, ampere, kelvin, mole, candela, unitless
2121
> , (~=)
2222
> , isZero
23-
> , (#)
23+
> , (#), (##)
2424
> , (+#), (-#), (*#), (/#)
2525
> , sinq, cosq, asinq, acosq, atanq, expq, logq
26+
> , qfold
2627
> ) where
2728

2829

@@ -340,26 +341,26 @@ The other functions can be written as similar power series and we'll see on thos
340341

341342
We quickly realize a pattern, so let's generalize a bit.
342343

343-
> qmap :: (a -> b) -> Quantity One a -> Quantity One b
344-
> qmap f (ValQuantity d1 v) = ValQuantity d1 (f v)
344+
> qmap :: (a -> b) -> Quantity dim a -> Quantity dim b
345+
> qmap f (ValQuantity d v) = ValQuantity d (f v)
345346

346-
> qmap' :: (a -> b) -> Quantity dim a -> Quantity dim b
347-
> qmap' f (ValQuantity d v) = ValQuantity d (f v)
347+
> instance Functor (Quantity d) where
348+
> fmap = qmap
348349

349350
> qfold :: (a -> a -> b) -> Quantity dim a -> Quantity dim a -> Quantity dim b
350351
> qfold f (ValQuantity d v1) (ValQuantity _ v2) = ValQuantity d (f v1 v2)
351352

352353
> sinq, cosq, asinq, acosq, atanq, expq, logq :: (Floating v) =>
353354
> Quantity One v -> Quantity One v
354-
> sinq = qmap sin
355-
> cosq = qmap cos
356-
> asinq = qmap asin
357-
> acosq = qmap acos
358-
> atanq = qmap atan
359-
> expq = qmap exp
360-
> logq = qmap log
355+
> sinq = fmap sin
356+
> cosq = fmap cos
357+
> asinq = fmap asin
358+
> acosq = fmap acos
359+
> atanq = fmap atan
360+
> expq = fmap exp
361+
> logq = fmap log
361362

362-
Why not make `Quantity` an instance of `Num`, `Fractional`, `Floating` och `Functor`? The reason is that the functions of those type classes have the following type
363+
Why not make `Quantity` an instance of `Num`, `Fractional` and `Floating`? The reason is that the functions of those type classes have the following type
363364

364365
< (*) :: (Num a) => a -> a -> a
365366

@@ -372,7 +373,7 @@ The input here may actually be of *different* types, and the output has a type d
372373

373374
However, operations with only scalars (type `One`) has types compatible with `Num`.
374375

375-
**Exercise** `Quantity One` has compatible types. Make it an instance of `Num`, `Fractional`, `Floating` and `Functor`.
376+
**Exercise** `Quantity One` has compatible types. Make it an instance of `Num`, `Fractional` and `Floating`.
376377

377378
<details>
378379
<summary>**Solution**</summary>
@@ -382,8 +383,8 @@ However, operations with only scalars (type `One`) has types compatible with `Nu
382383
> (+) = (+#)
383384
> (-) = (-#)
384385
> (*) = (*#)
385-
> abs = qmap abs
386-
> signum = qmap signum
386+
> abs = fmap abs
387+
> signum = fmap signum
387388
> fromInteger n = ValQuantity V.one (fromInteger n)
388389

389390
> instance (Fractional v) => Fractional (Quantity One v) where
@@ -399,14 +400,11 @@ However, operations with only scalars (type `One`) has types compatible with `Nu
399400
> asin = asinq
400401
> acos = acosq
401402
> atan = atanq
402-
> sinh = qmap sinh
403-
> cosh = qmap cosh
404-
> asinh = qmap asinh
405-
> acosh = qmap acosh
406-
> atanh = qmap atanh
407-
408-
> instance Functor (Quantity One) where
409-
> fmap = qmap
403+
> sinh = fmap sinh
404+
> cosh = fmap cosh
405+
> asinh = fmap asinh
406+
> acosh = fmap acosh
407+
> atanh = fmap atanh
410408

411409
</div>
412410
</details>
@@ -463,9 +461,18 @@ To solve these two problems we'll introduce some syntactic sugar. First some pre
463461

464462
And now the sugar.
465463

464+
> infixl 3 #
466465
> (#) :: (Num v) => v -> Quantity d v -> Quantity d v
467466
> v # (ValQuantity d bv) = ValQuantity d (v*bv)
468467

468+
\ignore{
469+
470+
> infixl 3 ##
471+
> (##) :: v -> Quantity d v -> Quantity d v
472+
> v ## (ValQuantity d _) = ValQuantity d v
473+
474+
}
475+
469476
The intended usage of the function is the following
470477

471478
< ghci> let myDistance = 5 # length
Lines changed: 202 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,202 @@
1+
2+
{-# LANGUAGE UndecidableInstances #-}
3+
{-# LANGUAGE FlexibleInstances #-}
4+
{-# LANGUAGE GADTs #-}
5+
{-# LANGUAGE DataKinds #-}
6+
{-# LANGUAGE TypeOperators #-}
7+
{-# LANGUAGE KindSignatures #-}
8+
9+
{-# LANGUAGE MultiParamTypeClasses #-}
10+
11+
module Dimensions.QuantityExtended where
12+
13+
import qualified Dimensions.ValueLevel as V
14+
import Dimensions.TypeLevel as T
15+
import Prelude as P hiding (length)
16+
17+
----------------------------------------
18+
-- Än så länge inget nytt
19+
----------------------------------------
20+
21+
data Quantity (d :: T.Dim) (v :: *) where
22+
ValQuantity :: V.Dim -> v -> Quantity d v
23+
24+
showQuantity :: (Show v) => Quantity d v -> String
25+
showQuantity (ValQuantity d v) = show v ++ " " ++ show d
26+
27+
instance (Show v) => Show (Quantity d v) where
28+
show = showQuantity
29+
30+
instance (Eq v) => Eq (Quantity d v) where
31+
(ValQuantity _ v1) == (ValQuantity _ v2) = v1 == v2
32+
33+
instance (Ord v) => Ord (Quantity d v) where
34+
(ValQuantity _ v1) `compare` (ValQuantity _ v2) = v1 `compare` v2
35+
36+
instance Functor (Quantity d) where
37+
fmap f (ValQuantity d v) = ValQuantity d (f v)
38+
39+
----------------------------------------
40+
-- Socker
41+
----------------------------------------
42+
43+
infixl 3 ##
44+
(##) :: v -> Quantity d w -> Quantity d v
45+
v ## (ValQuantity d _) = ValQuantity d v
46+
47+
-- Dummy-värden med matchande värde/typ-nivå dimensioner
48+
-- med en dummy-typ.
49+
50+
length :: Quantity Length Double
51+
length = ValQuantity V.length 1.0
52+
mass :: Quantity Mass Double
53+
mass = ValQuantity V.mass 1.0
54+
time :: Quantity Time Double
55+
time = ValQuantity V.time 1.0
56+
57+
-- Med `##` kan en Quantity med vilken värdetyp som helst skapas
58+
-- med valfri dimension av ovanstående.
59+
60+
-- Om värdetypen ej stöder multiplikation och division kan
61+
-- dessa dummy-värden ändå göras så på, och därför kan man
62+
-- alltid få valfri dimension.
63+
64+
----------------------------------------
65+
-- Aritmetik
66+
----------------------------------------
67+
68+
-- En `Quantity` innehåller något av någon typ. Om och hur addition
69+
-- o.s.v. ser ut för den kan variera, så typen själv ska sköta det.
70+
-- Dessutom kan det var multiplikation mellan olika typer.
71+
72+
class Addable a b c where
73+
doAdd :: a -> b -> c
74+
75+
(+#) :: (Addable a b c) => Quantity d a ->
76+
Quantity d b ->
77+
Quantity d c
78+
(ValQuantity d a) +# (ValQuantity _ b) = ValQuantity d $ doAdd a b
79+
80+
-- Nedan går ej! Blir problem med Vector då. Vet ej varför.
81+
82+
-- Allt "numeriskt" är adderbart
83+
--instance (Num v) => Addable v v v where
84+
-- doAdd = (+)
85+
86+
----------
87+
88+
class Subable a b c where
89+
doSub :: a -> b -> c
90+
91+
(-#) :: (Subable a b c) => Quantity d a ->
92+
Quantity d b ->
93+
Quantity d c
94+
(ValQuantity d a) -# (ValQuantity _ b) = ValQuantity d $ doSub a b
95+
96+
--instance (Num v) => Subable v v v where
97+
-- doSub = (-)
98+
99+
----------
100+
101+
class Multiplicable a b c where
102+
doMul :: a -> b -> c
103+
104+
(*#) :: (Multiplicable a b c) => Quantity d1 a ->
105+
Quantity d2 b ->
106+
Quantity (d1 `Mul` d2) c
107+
(ValQuantity d1 a) *# (ValQuantity d2 b) = ValQuantity (d1 `V.mul` d2) $ doMul a b
108+
109+
--instance (Num v) => Multiplicable v v v where
110+
-- doMul = (*)
111+
112+
----------
113+
114+
class Divisionable a b c where
115+
doDiv :: a -> b -> c
116+
117+
(/#) :: (Divisionable a b c) => Quantity d1 a ->
118+
Quantity d2 b ->
119+
Quantity (d1 `Div` d2) c
120+
(ValQuantity d1 a) /# (ValQuantity d2 b) = ValQuantity (d1 `V.div` d2) $ doDiv a b
121+
122+
--instance (Fractional v) => Divisionable v v v where
123+
-- doMul = (*)
124+
125+
----------------------------------------
126+
-- Derivering och integrering
127+
----------------------------------------
128+
129+
-- Är själva grejen som finns i en Quantity deriverbar och
130+
-- integrerbar ska Quantityn med den i också vara det.
131+
132+
class Differentiable a b where
133+
doDif :: a -> b
134+
135+
diff :: (Differentiable a b) => Quantity d a -> Quantity (d `Div` time) b
136+
diff = fmap doDif
137+
138+
139+
140+
141+
142+
143+
144+
145+
146+
147+
148+
149+
150+
151+
152+
153+
154+
155+
156+
157+
158+
159+
160+
161+
162+
163+
164+
165+
166+
167+
168+
169+
170+
171+
172+
173+
174+
175+
176+
177+
178+
179+
180+
181+
182+
183+
184+
185+
186+
187+
188+
189+
190+
191+
192+
193+
194+
195+
196+
197+
198+
199+
200+
201+
202+

0 commit comments

Comments
 (0)