2016-12-28 11:19:14 +00:00
|
|
|
{-# LANGUAGE OverloadedStrings, RecordWildCards #-}
|
2016-12-26 21:26:25 +00:00
|
|
|
module Main where
|
|
|
|
|
2016-12-27 22:25:58 +00:00
|
|
|
import Affection
|
|
|
|
import qualified SDL
|
|
|
|
import GEGL
|
|
|
|
import BABL
|
|
|
|
|
|
|
|
import qualified Data.Map as M
|
|
|
|
|
|
|
|
import Control.Monad (when)
|
|
|
|
|
2016-12-28 13:17:37 +00:00
|
|
|
import System.Random (randomRIO)
|
|
|
|
|
2016-12-27 22:25:58 +00:00
|
|
|
import Debug.Trace
|
|
|
|
|
2016-12-26 21:26:25 +00:00
|
|
|
main :: IO ()
|
2016-12-27 22:25:58 +00:00
|
|
|
main = withAffection $ AffectionConfig
|
|
|
|
{ initComponents = All
|
|
|
|
, windowTitle = "Haskelloids"
|
|
|
|
, windowConfig = defaultWindow
|
|
|
|
, preLoop = return ()
|
|
|
|
, drawLoop = draw
|
|
|
|
, updateLoop = update
|
|
|
|
, loadState = load
|
|
|
|
, cleanUp = clean
|
|
|
|
}
|
|
|
|
|
|
|
|
load :: SDL.Surface -> IO UserData
|
|
|
|
load _ = do
|
|
|
|
traceM "loading"
|
|
|
|
root <- gegl_node_new
|
|
|
|
traceM "root node"
|
|
|
|
ship <- gegl_node_new_child root $ Operation "gegl:svg-load"
|
|
|
|
[ Property "path" $ PropertyString "assets/ship.svg"
|
|
|
|
, Property "width" $ PropertyInt 50
|
|
|
|
, Property "height" $ PropertyInt 50
|
|
|
|
]
|
2016-12-28 13:17:37 +00:00
|
|
|
pnop <- gegl_node_new_child root $ Operation "gegl:nop" []
|
|
|
|
hnop <- gegl_node_new_child root $ Operation "gegl:nop" []
|
|
|
|
sover <- gegl_node_new_child root $ defaultOverOperation
|
|
|
|
hover <- gegl_node_new_child root $ defaultOverOperation
|
|
|
|
pover <- gegl_node_new_child root $ defaultOverOperation
|
2016-12-27 22:25:58 +00:00
|
|
|
translate <- gegl_node_new_child root $ Operation "gegl:translate"
|
2016-12-28 13:58:21 +00:00
|
|
|
[ Property "x" $ PropertyDouble 375
|
|
|
|
, Property "y" $ PropertyDouble 275
|
2016-12-27 22:25:58 +00:00
|
|
|
, Property "sampler" $ PropertyInt $ fromEnum GeglSamplerCubic
|
|
|
|
]
|
|
|
|
rotate <- gegl_node_new_child root $ Operation "gegl:rotate"
|
|
|
|
[ Property "origin-x" $ PropertyDouble 25
|
|
|
|
, Property "origin-y" $ PropertyDouble 25
|
|
|
|
, Property "sampler" $ PropertyInt $ fromEnum GeglSamplerCubic
|
|
|
|
]
|
|
|
|
crop <- gegl_node_new_child root $ Operation "gegl:crop"
|
|
|
|
[ Property "width" $ PropertyDouble 800
|
|
|
|
, Property "height" $ PropertyDouble 600
|
|
|
|
]
|
|
|
|
buffer <- gegl_buffer_new (Just $ GeglRectangle 0 0 800 600) =<<
|
|
|
|
babl_format (PixelFormat BABL.RGBA CFfloat)
|
|
|
|
sink <- gegl_node_new_child root $ Operation "gegl:copy-buffer"
|
|
|
|
[ Property "buffer" $ PropertyBuffer buffer
|
|
|
|
]
|
2016-12-28 11:17:55 +00:00
|
|
|
gegl_node_link_many [ship, rotate, translate]
|
2016-12-28 13:17:37 +00:00
|
|
|
gegl_node_link_many [pover, hover, sover, crop, sink]
|
|
|
|
gegl_node_connect_to translate "output" sover "aux"
|
|
|
|
gegl_node_connect_to pnop "output" pover "aux"
|
|
|
|
gegl_node_connect_to hnop "output" hover "aux"
|
2016-12-27 22:25:58 +00:00
|
|
|
traceM "nodes complete"
|
|
|
|
myMap <- return $ M.fromList
|
|
|
|
[ (KeyRoot, root)
|
|
|
|
, (KeyTranslate, translate)
|
|
|
|
, (KeyRotate, rotate)
|
|
|
|
, (KeyShip, ship)
|
2016-12-28 13:17:37 +00:00
|
|
|
, (KeyPNop, pnop)
|
|
|
|
, (KeyHNop, hnop)
|
2016-12-27 22:25:58 +00:00
|
|
|
, (KeyCrop, crop)
|
2016-12-28 13:17:37 +00:00
|
|
|
, (KeyShipOver, sover)
|
2016-12-27 22:25:58 +00:00
|
|
|
, (KeySink, sink)
|
|
|
|
]
|
2016-12-28 13:17:37 +00:00
|
|
|
hs <- mapM (\_ -> do
|
|
|
|
px <- liftIO $ randomRIO (0, 800)
|
|
|
|
py <- liftIO $ randomRIO (0, 600)
|
2016-12-28 13:58:49 +00:00
|
|
|
vx <- liftIO $ randomRIO (-10, 10)
|
|
|
|
vy <- liftIO $ randomRIO (-10, 10)
|
2016-12-28 13:17:37 +00:00
|
|
|
div <- liftIO $ randomRIO (1, 2)
|
2016-12-28 13:58:49 +00:00
|
|
|
rot <- liftIO $ randomRIO (-2 * pi, 2 * pi)
|
|
|
|
pitch <- liftIO $ randomRIO (-2 * pi, 2 * pi)
|
2016-12-28 13:17:37 +00:00
|
|
|
tempRoot <- liftIO $ gegl_node_new
|
|
|
|
tempOver <- liftIO $ gegl_node_new_child tempRoot $ defaultOverOperation
|
|
|
|
tempText <- liftIO $ gegl_node_new_child tempRoot $ textOperation
|
|
|
|
[ Property "string" $ PropertyString "λ"
|
|
|
|
, Property "color" $ PropertyColor $ GEGL.RGBA 1 1 1 1
|
2016-12-28 13:58:49 +00:00
|
|
|
, Property "size" $ PropertyDouble 100
|
2016-12-28 13:17:37 +00:00
|
|
|
]
|
2016-12-28 13:58:49 +00:00
|
|
|
tempTrans <- liftIO $ gegl_node_new_child tempRoot $ Operation "gegl:translate"
|
|
|
|
[ Property "x" $ PropertyDouble px
|
|
|
|
, Property "y" $ PropertyDouble py
|
|
|
|
, Property "sampler" $ PropertyInt $ fromEnum GeglSamplerCubic
|
|
|
|
]
|
|
|
|
tempRot <- liftIO $ gegl_node_new_child tempRoot $ Operation "gegl:rotate"
|
|
|
|
[ Property "origin-x" $ PropertyDouble 50
|
|
|
|
, Property "origin-y" $ PropertyDouble 50
|
|
|
|
, Property "degrees" $ PropertyDouble rot
|
|
|
|
, Property "sampler" $ PropertyInt $ fromEnum GeglSamplerCubic
|
|
|
|
]
|
|
|
|
liftIO $ gegl_node_link_many [tempText, tempRot, tempTrans]
|
|
|
|
liftIO $ gegl_node_connect_to tempTrans "output" tempOver "aux"
|
2016-12-28 13:17:37 +00:00
|
|
|
return Haskelloid
|
|
|
|
{ hPos = (px, py)
|
|
|
|
, hVel = (vx, vy)
|
2016-12-28 13:58:49 +00:00
|
|
|
, hRot = rot
|
|
|
|
, hPitch = pitch
|
2016-12-28 13:17:37 +00:00
|
|
|
, hDiv = div
|
|
|
|
, hFlange = tempOver
|
|
|
|
, hNodeGraph = M.fromList
|
|
|
|
[ ("root", tempRoot)
|
|
|
|
, ("over", tempOver)
|
|
|
|
, ("text", tempText)
|
2016-12-28 13:58:49 +00:00
|
|
|
, ("trans", tempTrans)
|
|
|
|
, ("rot", tempRot)
|
2016-12-28 13:17:37 +00:00
|
|
|
]
|
|
|
|
}
|
|
|
|
) [1..5]
|
|
|
|
liftIO $ gegl_node_link_many $ map hFlange hs
|
|
|
|
liftIO $ gegl_node_link (last $ map hFlange hs) hnop
|
2016-12-27 22:25:58 +00:00
|
|
|
return $ UserData
|
|
|
|
{ nodeGraph = myMap
|
|
|
|
, ship = Ship
|
|
|
|
{ sPos = (400, 300)
|
|
|
|
, sVel = (0, 0)
|
|
|
|
, sRot = 0
|
|
|
|
, sFlange = rotate
|
|
|
|
}
|
|
|
|
, buffer = buffer
|
2016-12-28 13:17:37 +00:00
|
|
|
, shots = ParticleSystem (ParticleStorage Nothing []) pnop buffer
|
|
|
|
, haskelloids = hs
|
2016-12-27 22:25:58 +00:00
|
|
|
}
|
|
|
|
|
|
|
|
data UserData = UserData
|
|
|
|
{ nodeGraph :: M.Map NodeKey GeglNode
|
|
|
|
, ship :: Ship
|
|
|
|
, buffer :: GeglBuffer
|
2016-12-28 13:17:37 +00:00
|
|
|
, haskelloids :: [Haskelloid]
|
2016-12-28 11:19:14 +00:00
|
|
|
, shots :: ParticleSystem
|
|
|
|
-- , debris :: ParticleSystem
|
2016-12-27 22:25:58 +00:00
|
|
|
}
|
|
|
|
|
|
|
|
data Ship = Ship
|
|
|
|
{ sPos :: (Double, Double)
|
|
|
|
, sVel :: (Double, Double)
|
|
|
|
, sRot :: Double
|
|
|
|
, sFlange :: GeglNode
|
|
|
|
}
|
|
|
|
|
2016-12-28 13:17:37 +00:00
|
|
|
data Haskelloid = Haskelloid
|
|
|
|
{ hPos :: (Double, Double)
|
|
|
|
, hVel :: (Double, Double)
|
2016-12-28 13:58:49 +00:00
|
|
|
, hRot :: Double
|
|
|
|
, hPitch :: Double
|
2016-12-28 13:17:37 +00:00
|
|
|
, hDiv :: Int
|
|
|
|
, hFlange :: GeglNode
|
|
|
|
, hNodeGraph :: M.Map String GeglNode
|
|
|
|
}
|
|
|
|
|
2016-12-27 22:25:58 +00:00
|
|
|
data NodeKey
|
|
|
|
= KeyRoot
|
|
|
|
| KeyTranslate
|
|
|
|
| KeyRotate
|
|
|
|
| KeyShip
|
2016-12-28 13:17:37 +00:00
|
|
|
| KeyPNop
|
|
|
|
| KeyHNop
|
2016-12-27 22:25:58 +00:00
|
|
|
| KeyCrop
|
2016-12-28 13:17:37 +00:00
|
|
|
| KeyShipOver
|
2016-12-27 22:25:58 +00:00
|
|
|
| KeySink
|
|
|
|
deriving (Ord, Eq)
|
|
|
|
|
|
|
|
update :: Double -> Affection UserData ()
|
|
|
|
update sec = do
|
|
|
|
-- traceM $ (show $ 1 / sec) ++ " FPS"
|
|
|
|
ad <- get
|
|
|
|
evs <- SDL.pollEvents
|
|
|
|
mapM_ (\e ->
|
|
|
|
case SDL.eventPayload e of
|
|
|
|
SDL.KeyboardEvent dat ->
|
|
|
|
case (SDL.keysymKeycode $ SDL.keyboardEventKeysym dat) of
|
|
|
|
SDL.KeycodeLeft -> do
|
|
|
|
ud <- getAffection
|
|
|
|
when (SDL.keyboardEventKeyMotion dat == SDL.Pressed) $
|
|
|
|
putAffection ud
|
|
|
|
{ ship = (ship ud)
|
2016-12-28 11:19:32 +00:00
|
|
|
{ sRot = (sRot $ ship ud) + 180 * sec
|
2016-12-27 22:25:58 +00:00
|
|
|
}
|
|
|
|
}
|
|
|
|
SDL.KeycodeRight -> do
|
|
|
|
ud <- getAffection
|
|
|
|
when (SDL.keyboardEventKeyMotion dat == SDL.Pressed) $
|
|
|
|
putAffection ud
|
|
|
|
{ ship = (ship ud)
|
2016-12-28 11:19:32 +00:00
|
|
|
{ sRot = (sRot $ ship ud) - 180 * sec
|
2016-12-27 22:25:58 +00:00
|
|
|
}
|
|
|
|
}
|
|
|
|
SDL.KeycodeUp ->
|
|
|
|
when (SDL.keyboardEventKeyMotion dat == SDL.Pressed) $ do
|
|
|
|
ud <- getAffection
|
2016-12-28 11:19:32 +00:00
|
|
|
-- let vx = -10 * (sin (toR $ 2 * (sRot $ ship ud))) + fst (sVel $ ship ud)
|
|
|
|
-- vy = -10 * (cos (toR $ 2 * (sRot $ ship ud))) + snd (sVel $ ship ud)
|
|
|
|
let vx = -10 * (sin (toR $ (sRot $ ship ud))) + fst (sVel $ ship ud)
|
|
|
|
vy = -10 * (cos (toR $ (sRot $ ship ud))) + snd (sVel $ ship ud)
|
2016-12-27 22:25:58 +00:00
|
|
|
putAffection ud
|
|
|
|
{ ship = (ship ud)
|
|
|
|
{ sVel = (vx, vy)
|
|
|
|
}
|
|
|
|
}
|
2016-12-28 13:58:49 +00:00
|
|
|
traceM $ show (vx, vy) ++ " " ++ show (sRot $ ship ud)
|
2016-12-28 11:19:14 +00:00
|
|
|
SDL.KeycodeSpace ->
|
|
|
|
when (SDL.keyboardEventKeyMotion dat == SDL.Pressed) $ do
|
|
|
|
ud <- getAffection
|
|
|
|
ad <- get
|
|
|
|
tempRoot <- liftIO $ gegl_node_new
|
|
|
|
tempRect <- liftIO $ gegl_node_new_child tempRoot $ Operation "gegl:rectangle"
|
|
|
|
[ Property "x" $ (PropertyDouble $ (fst $ sPos $ ship ud) + 23)
|
|
|
|
, Property "y" $ (PropertyDouble $ (snd $ sPos $ ship ud) + 23)
|
|
|
|
, Property "width" $ PropertyDouble 4
|
|
|
|
, Property "height" $ PropertyDouble 4
|
|
|
|
, Property "color" $ PropertyColor $ (GEGL.RGBA 1 1 1 1)
|
|
|
|
]
|
|
|
|
tempOver <- liftIO $ gegl_node_new_child tempRoot $ defaultOverOperation
|
|
|
|
liftIO $ gegl_node_connect_to tempRect "output" tempOver "aux"
|
|
|
|
ips <- insertParticle (shots ud) $
|
|
|
|
Particle
|
2016-12-28 13:58:49 +00:00
|
|
|
{ particleTimeToLive = 5
|
2016-12-28 11:19:14 +00:00
|
|
|
, particleCreation = elapsedTime ad
|
|
|
|
, particlePosition =
|
|
|
|
( (fst $ sPos $ ship ud) + 23
|
|
|
|
, (snd $ sPos $ ship ud) + 23
|
|
|
|
)
|
|
|
|
, particleRotation = Rad 0
|
|
|
|
, particleVelocity =
|
|
|
|
-- ( (floor $ -200 * (sin $ toR $ (sRot $ ship ud) + (fst $ sVel $ ship ud)))
|
|
|
|
-- , (floor $ -200 * (cos $ toR $ (sRot $ ship ud) + (snd $ sVel $ ship ud)))
|
|
|
|
( (floor $ -200 * (sin $ toR $ sRot $ ship ud))
|
|
|
|
, (floor $ -200 * (cos $ toR $ sRot $ ship ud))
|
|
|
|
)
|
|
|
|
, particlePitchRate = Rad 0
|
|
|
|
, particleRootNode = tempRoot
|
|
|
|
, particleNodeGraph = M.fromList
|
|
|
|
[ ("root", tempRoot)
|
|
|
|
, ("over", tempOver)
|
|
|
|
, ("rect", tempRect)
|
|
|
|
]
|
|
|
|
, particleStackCont = tempOver
|
|
|
|
, particleDrawFlange = tempOver
|
|
|
|
}
|
|
|
|
putAffection $ ud
|
|
|
|
{ shots = ips
|
|
|
|
}
|
2016-12-27 22:25:58 +00:00
|
|
|
_ -> return ()
|
|
|
|
SDL.WindowClosedEvent _ -> do
|
|
|
|
traceM "seeya!"
|
|
|
|
put ad
|
|
|
|
{ quitEvent = True
|
|
|
|
}
|
|
|
|
_ -> return ()
|
|
|
|
) evs
|
|
|
|
ud2 <- getAffection
|
|
|
|
let nx = fst (sPos $ ship ud2) + (fst (sVel $ ship ud2)) * sec
|
|
|
|
ny = snd (sPos $ ship ud2) + (snd (sVel $ ship ud2)) * sec
|
2016-12-28 11:19:45 +00:00
|
|
|
(nnx, nny) = wrapAround (nx, ny) 50
|
2016-12-27 22:25:58 +00:00
|
|
|
liftIO $ gegl_node_set (nodeGraph ud2 M.! KeyTranslate) $ Operation "gegl:translate"
|
|
|
|
[ Property "x" $ PropertyDouble $ nnx
|
|
|
|
, Property "y" $ PropertyDouble $ nny
|
|
|
|
]
|
|
|
|
liftIO $ gegl_node_set (nodeGraph ud2 M.! KeyRotate) $ Operation "gegl:rotate"
|
|
|
|
[ Property "degrees" $ PropertyDouble $ sRot $ ship ud2
|
|
|
|
]
|
2016-12-28 11:19:14 +00:00
|
|
|
ups <- updateParticleSystem (shots ud2) sec shotsUpd shotsDraw
|
2016-12-28 13:17:37 +00:00
|
|
|
nhs <- mapM (updateHaskelloid sec) (haskelloids ud2)
|
2016-12-27 22:25:58 +00:00
|
|
|
putAffection ud2
|
|
|
|
{ ship = (ship ud2)
|
|
|
|
{ sPos = (nnx, nny)
|
|
|
|
}
|
2016-12-28 11:19:14 +00:00
|
|
|
, shots = ups
|
2016-12-28 13:17:37 +00:00
|
|
|
, haskelloids = nhs
|
2016-12-27 22:25:58 +00:00
|
|
|
}
|
|
|
|
|
2016-12-28 11:19:45 +00:00
|
|
|
wrapAround (nx, ny) width = (nnx, nny)
|
|
|
|
where
|
|
|
|
nnx =
|
|
|
|
if nx > 800
|
|
|
|
then nx - (800 + width)
|
|
|
|
else if nx < -width then nx + 800 + width else nx
|
|
|
|
nny =
|
|
|
|
if ny > 600
|
|
|
|
then ny - (600 + width)
|
|
|
|
else if ny < -width then ny + 600 + width else ny
|
|
|
|
|
2016-12-27 22:25:58 +00:00
|
|
|
draw :: Affection UserData ()
|
|
|
|
draw = do
|
|
|
|
traceM "drawing"
|
|
|
|
ud <- getAffection
|
|
|
|
liftIO $ gegl_node_process $ nodeGraph ud M.! KeySink
|
2016-12-27 23:30:32 +00:00
|
|
|
-- mintr <- liftIO $ gegl_rectangle_intersect
|
|
|
|
-- (GeglRectangle 0 0 800 600)
|
|
|
|
-- (GeglRectangle (floor $ fst $ sPos $ ship ud) (floor $ snd $ sPos $ ship ud) 50 50)
|
|
|
|
-- maybe (return ()) (\intr ->
|
|
|
|
-- present
|
|
|
|
-- (GeglRectangle (floor $ fst $ sPos $ ship ud) (floor $ snd $ sPos $ ship ud) 50 50)
|
|
|
|
-- (buffer ud)
|
|
|
|
-- False
|
|
|
|
-- ) mintr
|
|
|
|
-- XXX: above part crashes regularly for no apparent reason
|
2016-12-27 22:25:58 +00:00
|
|
|
present
|
|
|
|
(GeglRectangle 0 0 800 600)
|
|
|
|
(buffer ud)
|
|
|
|
False
|
|
|
|
|
|
|
|
clean :: UserData -> IO ()
|
|
|
|
clean ud = return ()
|
|
|
|
|
|
|
|
toR :: Double -> Double
|
|
|
|
toR deg = deg * pi / 180
|
2016-12-28 11:19:14 +00:00
|
|
|
|
|
|
|
shotsUpd :: Double -> Particle -> Affection UserData Particle
|
|
|
|
shotsUpd sec part@Particle{..} = do
|
|
|
|
let newX = (fst particlePosition) + sec * (fromIntegral $ fst particleVelocity)
|
|
|
|
newY = (snd particlePosition) + sec * (fromIntegral $ snd particleVelocity)
|
2016-12-28 13:58:49 +00:00
|
|
|
(nnx, nny) = wrapAround (newX, newY) 4
|
2016-12-28 11:19:14 +00:00
|
|
|
liftIO $ gegl_node_set (particleNodeGraph M.! "rect") $ Operation "gegl:rectangle"
|
2016-12-28 13:58:49 +00:00
|
|
|
[ Property "x" $ PropertyDouble $ nnx - 2
|
|
|
|
, Property "y" $ PropertyDouble $ nny - 2
|
2016-12-28 11:19:14 +00:00
|
|
|
]
|
|
|
|
return part
|
|
|
|
{ particlePosition = (nnx, nny)
|
|
|
|
}
|
|
|
|
|
|
|
|
shotsDraw :: GeglBuffer -> GeglNode -> Particle -> Affection UserData ()
|
|
|
|
shotsDraw buf node Particle{..} = do
|
2016-12-28 13:17:37 +00:00
|
|
|
-- present
|
|
|
|
-- (GeglRectangle (floor $ fst particlePosition - 2) (floor $ snd particlePosition - 2) 4 4)
|
|
|
|
-- buf
|
|
|
|
-- False
|
|
|
|
return ()
|
|
|
|
|
|
|
|
updateHaskelloid :: Double -> Haskelloid -> Affection UserData Haskelloid
|
2016-12-28 13:58:49 +00:00
|
|
|
updateHaskelloid sec h@Haskelloid{..} = do
|
|
|
|
let newX = (fst $ hPos) + sec * (fst $ hVel)
|
|
|
|
newY = (snd $ hPos) + sec * (snd $ hVel)
|
|
|
|
newRot = hRot + hPitch * sec
|
|
|
|
(nnx, nny) = wrapAround (newX, newY) (50 / fromIntegral hDiv)
|
|
|
|
liftIO $ gegl_node_set (hNodeGraph M.! "trans") $ Operation "gegl:translate"
|
|
|
|
[ Property "x" $ PropertyDouble $ nnx - (50 / fromIntegral hDiv)
|
|
|
|
, Property "y" $ PropertyDouble $ nny - (50 / fromIntegral hDiv)
|
|
|
|
]
|
|
|
|
liftIO $ gegl_node_set (hNodeGraph M.! "rot") $ Operation "gegl:rotate"
|
|
|
|
[ Property "degrees" $ PropertyDouble newRot
|
|
|
|
]
|
|
|
|
return h
|
|
|
|
{ hPos = (nnx, nny)
|
|
|
|
, hRot = newRot
|
|
|
|
}
|