Run and export to CSV
This commit is contained in:
parent
cbc770f340
commit
104ec50dcd
3 changed files with 44 additions and 14 deletions
23
app/Main.hs
23
app/Main.hs
|
@ -2,5 +2,26 @@ module Main where
|
||||||
|
|
||||||
import Lib
|
import Lib
|
||||||
|
|
||||||
|
import Linear.Affine
|
||||||
|
import Linear.V3
|
||||||
|
|
||||||
|
csvFromPoint :: Point V3 Double -> String
|
||||||
|
csvFromPoint (P (V3 x y z)) =
|
||||||
|
show x ++ "," ++ show y ++ "," ++ show z
|
||||||
|
|
||||||
|
csvFromBodies :: [Body] -> [String]
|
||||||
|
csvFromBodies [] = []
|
||||||
|
csvFromBodies (x:xs) =
|
||||||
|
(bodyName x ++ ","
|
||||||
|
++ (show $ bodyMass x) ++ ","
|
||||||
|
++ (csvFromPoint $ bodyPosition x) ++ "\n")
|
||||||
|
:(csvFromBodies xs)
|
||||||
|
|
||||||
|
steps :: Int -> Double -> [Body] -> IO ()
|
||||||
|
steps 0 _ _ = return ()
|
||||||
|
steps n dt bodies = do
|
||||||
|
putStr . concat $ map ((++) (show n ++ ",")) $ csvFromBodies bodies
|
||||||
|
steps (n-1) dt (updateAll dt bodies)
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = putStrLn "Hello"
|
main = steps 1000000 10 [sun, earth, moon]
|
||||||
|
|
|
@ -26,6 +26,7 @@ executable orbit-exe
|
||||||
ghc-options: -threaded -rtsopts -with-rtsopts=-N
|
ghc-options: -threaded -rtsopts -with-rtsopts=-N
|
||||||
build-depends: base
|
build-depends: base
|
||||||
, orbit
|
, orbit
|
||||||
|
, linear
|
||||||
default-language: Haskell2010
|
default-language: Haskell2010
|
||||||
|
|
||||||
test-suite orbit-test
|
test-suite orbit-test
|
||||||
|
|
34
src/Lib.hs
34
src/Lib.hs
|
@ -1,11 +1,17 @@
|
||||||
module Lib (
|
module Lib (
|
||||||
gravity,
|
gravity,
|
||||||
Body,
|
Body,
|
||||||
|
bodyName,
|
||||||
|
bodyMass,
|
||||||
|
bodyPosition,
|
||||||
|
bodySpeed,
|
||||||
bodyDistance,
|
bodyDistance,
|
||||||
field,
|
field,
|
||||||
acceleration,
|
acceleration,
|
||||||
update,
|
update,
|
||||||
b1, b2, b3
|
updateAll,
|
||||||
|
b1, b2, b3,
|
||||||
|
au, sun, earth, moon
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Linear.Vector
|
import Linear.Vector
|
||||||
|
@ -27,9 +33,10 @@ gravity = 6.67408e-11
|
||||||
|
|
||||||
-- Body
|
-- Body
|
||||||
data Body = Body {
|
data Body = Body {
|
||||||
bodyMass :: Double,
|
bodyName :: String,
|
||||||
bodyPosition :: Point V3 Double,
|
bodyMass :: Double, -- [kg]
|
||||||
bodySpeed :: V3 Double
|
bodyPosition :: Point V3 Double, -- [m]
|
||||||
|
bodySpeed :: V3 Double -- [m/s]
|
||||||
} deriving (Show, Eq)
|
} deriving (Show, Eq)
|
||||||
|
|
||||||
|
|
||||||
|
@ -64,9 +71,9 @@ acceleration body = foldr f (fromInteger 0)
|
||||||
|
|
||||||
-- Update speed and position with using a timestep dt
|
-- Update speed and position with using a timestep dt
|
||||||
update :: Double -> Body -> [Body] -> Body
|
update :: Double -> Body -> [Body] -> Body
|
||||||
update dt (Body m pos speed) neighbours =
|
update dt (Body name m pos speed) neighbours =
|
||||||
Body m newpos newspeed
|
Body name m newpos newspeed
|
||||||
where accel = acceleration (Body m pos speed) neighbours
|
where accel = acceleration (Body name m pos speed) neighbours
|
||||||
newspeed = speed + dt *^ accel
|
newspeed = speed + dt *^ accel
|
||||||
newpos = pos + dt *^ P newspeed
|
newpos = pos + dt *^ P newspeed
|
||||||
|
|
||||||
|
@ -85,13 +92,14 @@ updateAll dt bodies = aux [] [] bodies
|
||||||
-- EXAMPLES
|
-- EXAMPLES
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
|
|
||||||
b1 = Body 42 (P $ V3 0 0 0) (V3 0 0 0)
|
b1 = Body "b1" 42e12 (P $ V3 0 0 0) (V3 0 0 0)
|
||||||
b2 = Body 11 (P $ V3 1 2 3) (V3 0 0 0)
|
b2 = Body "b2" 11e12 (P $ V3 1 2 3) (V3 0 3e3 0)
|
||||||
b3 = Body 5 (P $ V3 5 2 1) (V3 0 0 0)
|
b3 = Body "b3" 5e12 (P $ V3 5 2 1) (V3 3e3 1e3 0)
|
||||||
|
|
||||||
-- Astronomical Unit
|
-- Astronomical Unit [m]
|
||||||
au :: Double
|
au :: Double
|
||||||
au = 149597870700
|
au = 149597870700
|
||||||
|
|
||||||
sun = Body 1.98855e30 (P $ V3 0 0 0) (V3 0 0 0)
|
sun = Body "Sun" 1.98855e30 (P $ V3 0 0 0) (V3 0 0 0)
|
||||||
earth = Body 8.97237e24 (P $ V3 au 0 0) (V3 0 29.78e3 0)
|
earth = Body "Earth" 8.97237e24 (P $ V3 au 0 0) (V3 0 29.78e3 0)
|
||||||
|
moon = Body "Moon" 7.342e22 (P $ V3 (au+384399e3) 0 0) (V3 0 (29.78e3+1022) 0)
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue