Skip to content

Commit c687c8e

Browse files
author
Oskar Lundström
committed
Kombination dim+calc, wrap/unwrap och typsäker derivering
1 parent 151082b commit c687c8e

File tree

2 files changed

+133
-1
lines changed

2 files changed

+133
-1
lines changed
Lines changed: 122 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,122 @@
1+
2+
{-# LANGUAGE TypeOperators #-}
3+
4+
module Combination.Combination
5+
(
6+
) where
7+
8+
import Vector.Vector
9+
import Calculus.FunExpr
10+
import Calculus.DifferentialCalc
11+
import Dimensions.Quantity
12+
import Dimensions.TypeLevel
13+
import Prelude hiding (length)
14+
15+
-- Calculus i Dimensions
16+
------------------------
17+
18+
instance Fractional FunExpr where
19+
fromRational = Const . fromRational
20+
(/) = (:/)
21+
22+
instance Floating FunExpr where
23+
pi = Const pi
24+
exp = (Exp :.)
25+
log = (Log :.)
26+
sin = (Sin :.)
27+
cos = (Cos :.)
28+
asin = (Asin :.)
29+
acos = (Acos :.)
30+
atan = undefined
31+
sinh = undefined
32+
cosh = undefined
33+
asinh = undefined
34+
acosh = undefined
35+
atanh = undefined
36+
37+
-- Ett flygplan med position 5+2t
38+
t1 :: Quantity Length FunExpr
39+
t1 = (Const 5 :+ Const 2 :* Id) # length
40+
41+
-- eller kortare
42+
type CQ d = Quantity d FunExpr
43+
44+
t2 :: CQ Length
45+
t2 = t1
46+
47+
-- Ett flygplan i turbulens
48+
t3 :: CQ Length
49+
t3 = 5 + sin Id # length
50+
51+
-- Ett flygplan som står stilla
52+
t4 :: CQ Length
53+
t4 = 8 # length
54+
55+
type Area = Length `Mul` Length
56+
57+
-- Någon slags multiplikation
58+
t5 :: CQ Area
59+
t5 = t1 *# t3
60+
61+
t6 :: CQ Area
62+
t6 = fmap simplify t5
63+
64+
-- Någon slags division
65+
t7 :: CQ Length
66+
t7 = t6 /# t4
67+
68+
-- Går ej, vilket är bra
69+
-- t8 :: CQ Area
70+
-- t8 = t6 /# t4
71+
72+
-- Stöd för derivering. Hela CQ och dessa
73+
-- bör vara dola för utomstående användare.
74+
-- Inuti är "otypat". Wrap och unwrap borde vara "protected" och inte "public", Java analogi.
75+
76+
differentiateWRTtime :: CQ d -> CQ (d `Div` Time)
77+
differentiateWRTtime cq = newWithNewQuantity
78+
where
79+
originalWithQuantity = cq
80+
newWithQuantity = fmap derive cq
81+
newWithoutQuantity = unwrap newWithQuantity
82+
newWithNewQuantity = wrap newWithoutQuantity (originalWithQuantity /# time)
83+
84+
85+
86+
87+
88+
89+
90+
91+
92+
93+
94+
95+
96+
97+
98+
99+
100+
101+
102+
103+
104+
105+
106+
107+
108+
109+
110+
111+
112+
113+
114+
115+
116+
117+
118+
119+
120+
121+
122+

Physics/src/Dimensions/Quantity.lhs

Lines changed: 11 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ Quantities
2020
> , meter, kilogram, second, ampere, kelvin, mole, candela, unitless
2121
> , (~=)
2222
> , isZero
23-
> , (#)
23+
> , (#), wrap, unwrap
2424
> , (+#), (-#), (*#), (/#)
2525
> , sinq, cosq, asinq, acosq, atanq, expq, logq
2626
> , qfold
@@ -465,6 +465,16 @@ And now the sugar.
465465
> (#) :: (Num v) => v -> Quantity d v -> Quantity d v
466466
> v # (ValQuantity d bv) = ValQuantity d (v*bv)
467467

468+
\ignore{
469+
470+
> wrap :: v -> Quantity d v -> Quantity d v
471+
> wrap v (ValQuantity d _) = ValQuantity d v
472+
473+
> unwrap :: Quantity d v -> v
474+
> unwrap (ValQuantity _ v) = v
475+
476+
}
477+
468478
The intended usage of the function is the following
469479

470480
< ghci> let myDistance = 5 # length

0 commit comments

Comments
 (0)