|
3 | 3 | {-# LANGUAGE MultiParamTypeClasses #-} |
4 | 4 | {-# LANGUAGE FlexibleInstances #-} |
5 | 5 |
|
6 | | -module Combination.Combination |
7 | | - ( |
8 | | - ) where |
| 6 | +module Combination.Combination where |
9 | 7 |
|
10 | 8 | import Vector.Vector2 |
11 | 9 | --import Calculus.FunExpr |
12 | 10 | --import Calculus.DifferentialCalc |
13 | 11 | --import Calculus.IntegralCalc |
14 | | -import Dimensions.Quantity2 |
| 12 | +import Combination.Quantity |
15 | 13 | import Dimensions.TypeLevel |
16 | 14 | import qualified Dimensions.ValueLevel as V |
17 | 15 | import Prelude hiding (length) |
18 | 16 |
|
19 | | --- Calculus i Dimensions |
20 | | ------------------------- |
21 | 17 |
|
22 | | -{- |
23 | 18 |
|
24 | | -instance Fractional FunExpr where |
25 | | - fromRational = Const . fromRational |
26 | | - (/) = (:/) |
27 | 19 |
|
28 | | -instance Floating FunExpr where |
29 | | - pi = Const pi |
30 | | - exp = (Exp :.) |
31 | | - log = (Log :.) |
32 | | - sin = (Sin :.) |
33 | | - cos = (Cos :.) |
34 | | - asin = (Asin :.) |
35 | | - acos = (Acos :.) |
36 | | - atan = undefined |
37 | | - sinh = undefined |
38 | | - cosh = undefined |
39 | | - asinh = undefined |
40 | | - acosh = undefined |
41 | | - atanh = undefined |
42 | | -
|
43 | | --- Ett flygplan med position 5+2t |
44 | | -t1 :: Quantity Length FunExpr |
45 | | -t1 = (Const 5 :+ Const 2 :* Id) # length |
46 | | -
|
47 | | --- eller kortare |
48 | | -type QC d = Quantity d FunExpr |
49 | | -
|
50 | | -t2 :: QC Length |
51 | | -t2 = t1 |
52 | | -
|
53 | | --- Ett flygplan i turbulens |
54 | | -t3 :: QC Length |
55 | | -t3 = 5 + sin Id # length |
56 | | -
|
57 | | --- Ett flygplan som står stilla |
58 | | -t4 :: QC Length |
59 | | -t4 = 8 # length |
60 | | -
|
61 | | -type Area = Length `Mul` Length |
62 | | -
|
63 | | --- Någon slags multiplikation |
64 | | -t5 :: QC Area |
65 | | -t5 = t1 *# t3 |
66 | | -
|
67 | | -t6 :: QC Area |
68 | | -t6 = fmap simplify t5 |
69 | | -
|
70 | | --- Någon slags division |
71 | | -t7 :: QC Length |
72 | | -t7 = t6 /# t4 |
73 | | -
|
74 | | --- Går ej, vilket är bra |
75 | | --- t8 :: QC Area |
76 | | --- t8 = t6 /# t4 |
77 | | -
|
78 | | --- Stöd för derivering. Hela QC och dessa |
79 | | --- bör vara dola för utomstående användare. |
80 | | -
|
81 | | --- fmap på Quantity, men inte QC! |
82 | | -
|
83 | | -differentiateWRTtime :: QC d -> QC (d `Div` Time) |
84 | | -differentiateWRTtime qc = fmap simplify $ fmap derive qc /# time |
85 | | -
|
86 | | -integrateWRTtime :: QC d -> QC (d `Mul` Time) |
87 | | -integrateWRTtime qc = fmap simplify $ fmap integrate qc *# time |
88 | | -
|
89 | | --} |
90 | | - |
91 | | - |
92 | | --------------------- |
93 | | --- Calc i Vec i Quan |
94 | | --------------------- |
95 | | - |
96 | | ------------------------ |
97 | | --- Instansiering |
98 | | - |
99 | | --- En vektor kan adderas |
100 | | - |
101 | | --- (Kan alla göras samtidigt?) |
102 | | - |
103 | | -instance (Addable v v v) => Addable (Vector2 v) (Vector2 v) (Vector2 v) where |
104 | | - doAdd = vzipWith (doAdd) |
105 | | -instance (Addable v v v) => Addable (Vector3 v) (Vector3 v) (Vector3 v) where |
106 | | - doAdd = vzipWith (doAdd) |
107 | | - |
108 | | --- En vektor kan multipliceras på flera sätt |
109 | | - |
110 | | --- Skalning (från vänster) |
111 | | -instance (Num v) => Multiplicable v (Vector2 v) (Vector2 v) where |
112 | | - doMult = scale |
113 | | -instance (Num v) => Multiplicable v (Vector3 v) (Vector3 v) where |
114 | | - doMult = scale |
115 | | - |
116 | | --- Kryssprdoukt |
117 | | -instance (Num v) => Multiplicable (Vector3 v) (Vector3 v) (Vector3 v) where |
118 | | - doMult = crossProd |
119 | | - |
120 | | --- Skalärprodukt |
121 | | -instance (Num v) => Multiplicable (Vector2 v) (Vector2 v) v where |
122 | | - doMult = dotProd |
123 | | -instance (Num v) => Multiplicable (Vector3 v) (Vector3 v) v where |
124 | | - doMult = dotProd |
125 | | - |
126 | | --- En vektor kan "skapas" |
127 | | - |
128 | | -instance (Creatable v) => Creatable (Vector2 v) where |
129 | | - anyVal = V2 anyVal anyVal |
130 | | -instance (Creatable v) => Creatable (Vector3 v) where |
131 | | - anyVal = V3 anyVal anyVal anyVal |
132 | | - |
133 | | ------------------------------------- |
134 | | --- Användning |
135 | | - |
136 | | --- Ej dimensionssäkra |
137 | | -v1 :: Vector3 Double |
138 | | -v1 = V3 3 2 3 |
139 | | -v2 :: Vector3 Double |
140 | | -v2 = V3 1 2 5 |
141 | | -v3 :: Vector3 Double |
142 | | -v3 = V3 7 8 2 |
143 | | - |
144 | | --- Dimensionsäkra |
145 | | -v1d :: Quantity Length (Vector3 Double) |
146 | | -v1d = v1 ## length |
147 | | -v2d :: Quantity Mass (Vector3 Double) |
148 | | -v2d = v2 ## mass |
149 | | -v3d :: Quantity Time (Vector3 Double) |
150 | | -v3d = v3 ## time |
151 | | - |
152 | | --- t1 kräver typsignatur, antagligen för den här MultiParam... |
153 | | --- så att ska veta vilken instans |
154 | | - |
155 | | --- Addition |
156 | | -t1 :: Quantity Length (Vector3 Double) |
157 | | -t1 = v1d +# v1d |
158 | | - |
159 | | --- Kryssprodukt |
160 | | -t2 :: Quantity (Length `Mul` Mass) (Vector3 Double) |
161 | | -t2 = v1d *# v2d |
162 | | - |
163 | | --- Skalning |
164 | | -t3 :: Quantity (Length `Mul` Mass) (Vector3 Double) |
165 | | -t3 = s *# v2d |
166 | | - where |
167 | | - s :: Quantity Length Double |
168 | | - s = 3.0 ## length |
169 | | - |
170 | | --- Skalärprodukt |
171 | | -t4 :: Quantity (Time `Mul` Length) Double |
172 | | -t4 = v3d *# v1d |
173 | 20 |
|
174 | 21 |
|
175 | 22 |
|
|
0 commit comments