Haddock documentation

This commit is contained in:
Dimitri Lozeve 2017-07-26 09:35:29 +02:00
parent 7be6f684d4
commit b3854f6841

View file

@ -1,12 +1,23 @@
{-|
Module : Lib
Description : N-body simulation
Copyright : (c) Dimitri Lozeve, 2017
License : BSD3
Maintainer : dimitri.lozeve@gmail.com
-}
module Lib ( module Lib (
-- * Constants
gravity, gravity,
-- * Body type
Body(..), Body(..),
bodyDistance, bodyDistance,
-- * Gravity force
field, field,
acceleration, acceleration,
-- * Simulation
update, update,
updateAll, updateAll,
b1, b2, b3, -- * Examples
au, sun, earth, moon, mercury, venus, mars au, sun, earth, moon, mercury, venus, mars
) where ) where
@ -19,7 +30,7 @@ import Linear.Metric
-- CONSTANTS -- CONSTANTS
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Gravitational constant [m^3 kg^-1 s^-2] -- | Gravitational constant [m^3 kg^-1 s^-2]
gravity :: Double gravity :: Double
gravity = 6.67408e-11 gravity = 6.67408e-11
@ -27,17 +38,17 @@ gravity = 6.67408e-11
-- BODY TYPE -- BODY TYPE
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Body -- | Body type
data Body = Body { data Body = Body {
bodyName :: String, bodyName :: String, -- ^ Name
bodyRadius :: Double, -- [m] bodyRadius :: Double, -- ^ Radius [m]
bodyMass :: Double, -- [kg] bodyMass :: Double, -- ^ Mass [kg]
bodyPosition :: Point V3 Double, -- [m] bodyPosition :: Point V3 Double, -- ^ Position [m]
bodySpeed :: V3 Double -- [m/s] bodySpeed :: V3 Double -- ^ Speed [m/s]
} deriving (Show, Eq) } deriving (Show, Eq)
-- Distance between two bodies -- | Distance between two bodies
bodyDistance :: Body -> Body -> Double bodyDistance :: Body -> Body -> Double
bodyDistance body1 body2 = bodyDistance body1 body2 =
distance (bodyPosition body1) (bodyPosition body2) distance (bodyPosition body1) (bodyPosition body2)
@ -47,7 +58,7 @@ bodyDistance body1 body2 =
-- GRAVITY FORCE -- GRAVITY FORCE
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Field created by a body on a certain position -- | Field created by a body on a certain position
field :: Body -> Point V3 Double -> V3 Double field :: Body -> Point V3 Double -> V3 Double
field body pos = field body pos =
unP $ (gravity * m / r**2) *^ normalize vec unP $ (gravity * m / r**2) *^ normalize vec
@ -55,7 +66,7 @@ field body pos =
vec = bodyPosition body - pos vec = bodyPosition body - pos
r = norm vec r = norm vec
-- Acceleration given to a body by its neighbours -- | Acceleration given to a body by its neighbours
acceleration :: Body -> [Body] -> V3 Double acceleration :: Body -> [Body] -> V3 Double
acceleration body = foldr f 0 acceleration body = foldr f 0
where f neighbour acc = where f neighbour acc =
@ -66,15 +77,18 @@ acceleration body = foldr f 0
-- SIMULATION -- SIMULATION
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Update speed and position with using a timestep dt -- | Update speed and position
update :: Double -> Body -> [Body] -> Body update :: Double -- ^ The time step
-> Body -- ^ The body to update
-> [Body] -- ^ The Body's neighbours
-> Body -- ^ The updated Body
update dt (Body name r m pos speed) neighbours = update dt (Body name r m pos speed) neighbours =
Body name r m newpos newspeed Body name r m newpos newspeed
where accel = acceleration (Body name r m pos speed) neighbours where accel = acceleration (Body name r m pos speed) neighbours
newspeed = speed + dt *^ accel newspeed = speed + dt *^ accel
newpos = pos + dt *^ P newspeed newpos = pos + dt *^ P newspeed
-- Update all bodies with a timestep dt -- | Update all bodies with a timestep dt
updateAll :: Double -> [Body] -> [Body] updateAll :: Double -> [Body] -> [Body]
updateAll dt = aux [] [] updateAll dt = aux [] []
where where
@ -89,17 +103,19 @@ updateAll dt = aux [] []
-- EXAMPLES -- EXAMPLES
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
b1 = Body "b1" 1 42e12 (P $ V3 0 0 0) (V3 0 0 0) -- | Astronomical Unit [m]
b2 = Body "b2" 1 11e12 (P $ V3 1 2 3) (V3 0 3e3 0)
b3 = Body "b3" 1 5e12 (P $ V3 5 2 1) (V3 3e3 1e3 0)
-- Astronomical Unit [m]
au :: Double au :: Double
au = 149597870700 au = 149597870700
-- | The Sun
sun = Body "Sun" 695700000 1.98855e30 (P $ V3 0 0 0) (V3 0 0 0) sun = Body "Sun" 695700000 1.98855e30 (P $ V3 0 0 0) (V3 0 0 0)
-- | The Earth
earth = Body "Earth" 6.371e6 8.97237e24 (P $ V3 au 0 0) (V3 0 29.78e3 0) earth = Body "Earth" 6.371e6 8.97237e24 (P $ V3 au 0 0) (V3 0 29.78e3 0)
-- | The Moon
moon = Body "Moon" 1.7371e6 7.342e22 (P $ V3 (au+384399e3) 0 0) (V3 0 (29.78e3+1022) 0) moon = Body "Moon" 1.7371e6 7.342e22 (P $ V3 (au+384399e3) 0 0) (V3 0 (29.78e3+1022) 0)
-- | Mercury
mercury = Body "Mercury" 2.4397e6 3.3011e23 (P $ V3 57909050000 0 0) (V3 0 47362 0) mercury = Body "Mercury" 2.4397e6 3.3011e23 (P $ V3 57909050000 0 0) (V3 0 47362 0)
-- | Venus
venus = Body "Venus" 6.0518e6 4.8675e24 (P $ V3 108208000000 0 0) (V3 0 35.02e3 0) venus = Body "Venus" 6.0518e6 4.8675e24 (P $ V3 108208000000 0 0) (V3 0 35.02e3 0)
-- | Mars
mars = Body "Mars" 3.3895e6 6.4171e23 (P $ V3 227.9392e9 0 0) (V3 0 24.077e3 0) mars = Body "Mars" 3.3895e6 6.4171e23 (P $ V3 227.9392e9 0 0) (V3 0 24.077e3 0)