Skip to content

Commit 38ef949

Browse files
author
Oskar Lundström
committed
Gjorde vektorer kompatibla med dim-gränssnitt
1 parent b445434 commit 38ef949

File tree

5 files changed

+213
-219
lines changed

5 files changed

+213
-219
lines changed

Physics/src/Combination/Combination.hs

Lines changed: 2 additions & 155 deletions
Original file line numberDiff line numberDiff line change
@@ -3,173 +3,20 @@
33
{-# LANGUAGE MultiParamTypeClasses #-}
44
{-# LANGUAGE FlexibleInstances #-}
55

6-
module Combination.Combination
7-
(
8-
) where
6+
module Combination.Combination where
97

108
import Vector.Vector2
119
--import Calculus.FunExpr
1210
--import Calculus.DifferentialCalc
1311
--import Calculus.IntegralCalc
14-
import Dimensions.Quantity2
12+
import Combination.Quantity
1513
import Dimensions.TypeLevel
1614
import qualified Dimensions.ValueLevel as V
1715
import Prelude hiding (length)
1816

19-
-- Calculus i Dimensions
20-
------------------------
2117

22-
{-
2318

24-
instance Fractional FunExpr where
25-
fromRational = Const . fromRational
26-
(/) = (:/)
2719

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
17320

17421

17522

Physics/src/Combination/MWE.hs

Lines changed: 0 additions & 58 deletions
This file was deleted.

Physics/src/Dimensions/QuantityExtended.hs renamed to Physics/src/Combination/Quantity.hs

Lines changed: 30 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@
88

99
{-# LANGUAGE MultiParamTypeClasses #-}
1010

11-
module Dimensions.QuantityExtended where
11+
module Combination.Quantity where
1212

1313
import qualified Dimensions.ValueLevel as V
1414
import Dimensions.TypeLevel as T
@@ -120,7 +120,7 @@ class Divisionable a b c where
120120
(ValQuantity d1 a) /# (ValQuantity d2 b) = ValQuantity (d1 `V.div` d2) $ doDiv a b
121121

122122
--instance (Fractional v) => Divisionable v v v where
123-
-- doMul = (*)
123+
-- doDiv = (/)
124124

125125
----------------------------------------
126126
-- Derivering och integrering
@@ -129,12 +129,36 @@ class Divisionable a b c where
129129
-- Är själva grejen som finns i en Quantity deriverbar och
130130
-- integrerbar ska Quantityn med den i också vara det.
131131

132-
class Differentiable a b where
133-
doDif :: a -> b
132+
class Calculable v where
133+
doDif :: v -> v
134+
doInteg :: v -> v
135+
136+
diff :: (Calculable v) => Quantity d v -> Quantity (d `Div` Time) v
137+
diff (ValQuantity d v) = ValQuantity (d `V.div` V.time) $ doDif v
138+
139+
-- Inte det snyggaste...
140+
141+
integ :: (Calculable v) => Quantity d v -> Quantity (d `Mul` Time) v
142+
integ (ValQuantity d v) = ValQuantity (d `V.mul` V.time) $ doInteg v
143+
144+
----------------------------------------
145+
-- Hack
146+
----------------------------------------
147+
148+
-- Eftersom det blir problem med Num som instans av många
149+
-- görs här manuellt för vissa datatyper
150+
151+
instance Addable Double Double Double where
152+
doAdd = (+)
153+
154+
instance Subable Double Double Double where
155+
doSub = (-)
134156

135-
diff :: (Differentiable a b) => Quantity d a -> Quantity (d `Div` time) b
136-
diff = fmap doDif
157+
instance Multiplicable Double Double Double where
158+
doMul = (*)
137159

160+
instance Divisionable Double Double Double where
161+
doDiv = (/)
138162

139163

140164

0 commit comments

Comments
 (0)