Refactored world runner.
[hollow-plutonium.git] / Path.hs
blob89aea0c9009a1f90b8e59f18effccafc14c527f8
1 module Path where
3 import Data.Complex
4 import Data.Monoid
5 import Data.List
7 import Coord
9 -- a Path is a list of locations
10 -- it represents the discrete motion of an object starting from now
11 -- the [] path means the object does not exist
12 -- therefore a finite path manifests itself as an object that moves
13 -- in some way and finally disappears.
15 -- the Monoid instance allows you to compose Paths. This is a sum-type
16 -- composition, mappend p1 p2 is a path that follows p1 + p2 and either
17 -- ends when p1 or p2 ends (whichever comes first) or does not end in
18 -- the case p1 and p2 are infinite. the identity path is repeat 0, i.e.
19 -- does not move from the origin or disappear ever.
21 -- the origin. there is only one origin. in order to shift a path away
22 -- from the origin by amount x, mappend (repeat x).
24 type Path a = [a]
27 pempty :: Path a
28 pempty = []
30 pappend :: (Num a) => Path a -> Path a -> Path a
31 pappend [] _ = []
32 pappend _ [] = []
33 pappend (x:xs) (y:ys) = (x+y) : pappend xs ys
35 pconcat :: (Num a) => [Path a] -> Path a
36 pconcat xs = foldl pappend (repeat 0) xs
39 at :: a -> Path a
40 at x = repeat x
42 ray :: (Fractional a) => a -> Path a
43 ray v = map ((*) (v/100) . fromIntegral) [0..]
45 segment :: (Fractional a) => a -> a -> Path a
46 segment x 0 = []
47 segment x speed = []
49 left = segment (1:+0) 1
50 right = segment ((-1):+0) 1
51 up = segment (0:+1) 1
52 down = segment (0:+(-1)) 1
54 timeWarp :: (Fractional a) => a -> Path a -> Path a
55 timeWarp s ps = ps
57 forNext :: Int -> Path a -> Path a
58 forNext l ps = take l ps
60 (&>) :: (Num a) => Path a -> Path a -> Path a
61 xs &> ys = f xs ys where
62 f [] _ = []
63 f [x] ys = x : map (+x) ys
64 f (x:xs) ys = x : f xs ys
66 circle :: Spin -> Radius -> Path Coord
67 circle 0 r = at (r:+0)
68 circle w r = map f xs where
69 f = mkPolar r . (\x -> 2 * pi * x / steps)
70 xs = [0..steps-1]
71 steps = 100 / w
73 freeze :: Path a -> Path a
74 freeze (x:_) = at x