Day 20 - replaced custom Property data type with Vector.V3 to avoid having to define vector addition and scalar multiplication myself
This commit is contained in:
parent
c3c22a5f8f
commit
ddd8e7537d
32
20.hs
32
20.hs
|
@ -2,35 +2,33 @@ import Data.List.Split (splitOn)
|
|||
import Data.List (elemIndex, sortOn, groupBy)
|
||||
import Data.Monoid ((<>))
|
||||
import Data.Function (on)
|
||||
import Data.Vector.Class
|
||||
import Data.Vector.V3
|
||||
|
||||
data Property = Property Int Int Int deriving (Eq, Ord)
|
||||
data Particle = Particle {
|
||||
position :: Property,
|
||||
velocity :: Property,
|
||||
acceleration :: Property
|
||||
position :: Vector3,
|
||||
velocity :: Vector3,
|
||||
acceleration :: Vector3
|
||||
}
|
||||
|
||||
instance Monoid Property where
|
||||
mempty = Property 0 0 0
|
||||
Property x1 y1 z1 `mappend` Property x2 y2 z2 = Property (x1 + x2) (y1 + y2) (z1 + z2)
|
||||
instance Ord Vector3 where
|
||||
Vector3 x1 y1 z1 `compare` Vector3 x2 y2 z2 = compare x1 x2 <> compare y1 y2 <> compare z1 z2
|
||||
|
||||
distance :: Particle -> Int
|
||||
distance (Particle (Property x y z) _ _) = abs x + abs y + abs z
|
||||
norm :: Vector3 -> Double
|
||||
norm (Vector3 x y z) = abs x + abs y + abs z
|
||||
|
||||
updateParticle :: Int -> Particle -> Particle
|
||||
updateParticle :: Double -> Particle -> Particle
|
||||
updateParticle t (Particle p v a) =
|
||||
Particle (p <> t *** v <> (t * t `div` 2) *** a) (v <> t *** a) a
|
||||
where n *** (Property x y z) = Property (n * x) (n * y) (n * z)
|
||||
Particle (p + t *| v + (t * (t + 1) / 2) *| a) (v + t *| a) a
|
||||
|
||||
stepParticles :: [Particle] -> [Particle]
|
||||
stepParticles particles =
|
||||
concat . filter ((== 1) . length) . groupBy ((==) `on` position) . sortOn position . map step $ particles
|
||||
where step (Particle p v a) = Particle (p <> v <> a) (v <> a) a
|
||||
concat . filter ((== 1) . length) . groupBy ((==) `on` position) . sortOn position . map (updateParticle 1) $ particles
|
||||
|
||||
parseProperty :: String -> Property
|
||||
parseProperty :: String -> Vector3
|
||||
parseProperty str =
|
||||
let x : y : z : [] = map read . splitOn "," . drop 3 . init $ str
|
||||
in Property x y z
|
||||
in Vector3 x y z
|
||||
|
||||
parseLine :: String -> Particle
|
||||
parseLine str =
|
||||
|
@ -40,6 +38,6 @@ parseLine str =
|
|||
main :: IO ()
|
||||
main = do
|
||||
particles <- map parseLine . lines <$> readFile "20.txt"
|
||||
let distances = map (distance . updateParticle 400) particles
|
||||
let distances = map (norm . position . updateParticle 400) particles
|
||||
print $ elemIndex (minimum distances) distances
|
||||
print $ length $ iterate stepParticles particles !! 40
|
Loading…
Reference in New Issue