2016-12-13 10:08:49 +00:00
|
|
|
{-# LANGUAGE RecordWildCards #-}
|
2017-02-25 16:23:28 +00:00
|
|
|
{-# LANGUAGE BangPatterns #-}
|
2016-12-13 10:08:49 +00:00
|
|
|
|
2016-12-12 02:34:57 +00:00
|
|
|
-- | This module introduces a simple particle system to Affection
|
|
|
|
module Affection.Particle
|
2016-12-13 10:08:49 +00:00
|
|
|
( updateParticle
|
2016-12-12 02:34:57 +00:00
|
|
|
, drawParticles
|
2016-12-13 10:08:49 +00:00
|
|
|
, updateParticleSystem
|
2016-12-25 07:14:51 +00:00
|
|
|
, insertParticle
|
2016-12-12 02:34:57 +00:00
|
|
|
) where
|
|
|
|
|
|
|
|
import Affection.Types
|
|
|
|
|
2016-12-23 13:18:39 +00:00
|
|
|
import Control.Monad
|
2016-12-25 07:14:51 +00:00
|
|
|
import Control.Monad.State (get)
|
2016-12-23 13:18:39 +00:00
|
|
|
|
|
|
|
import Data.Maybe
|
2016-12-13 10:08:49 +00:00
|
|
|
|
|
|
|
import qualified GEGL as G
|
|
|
|
|
2016-12-24 07:27:47 +00:00
|
|
|
import Debug.Trace
|
|
|
|
|
2016-12-12 02:34:57 +00:00
|
|
|
-- This function updates particles through a specified function. Particle ageing
|
|
|
|
-- and death is being handled by 'updateParticles' itself and does not need to
|
|
|
|
-- bother you.
|
2016-12-13 10:08:49 +00:00
|
|
|
updateParticle
|
2016-12-24 00:13:00 +00:00
|
|
|
:: Double
|
|
|
|
-- ^ Elapsed time in seconds
|
|
|
|
-> (Double -> Particle -> Affection us Particle)
|
|
|
|
-- ^ Update function for a single 'Particle'
|
|
|
|
-- This Function should take the elapsed time
|
|
|
|
-- in seconds and the initial particle as arguments.
|
2016-12-25 07:14:51 +00:00
|
|
|
-- -> [Maybe Particle]
|
2016-12-24 00:13:00 +00:00
|
|
|
-> Particle
|
|
|
|
-- ^ 'Particle' to be processed
|
2016-12-25 07:14:51 +00:00
|
|
|
-- -> Affection us [Maybe Particle]
|
|
|
|
-> Affection us (Maybe Particle)
|
2016-12-24 00:13:00 +00:00
|
|
|
-- ^ resulting 'Particle'
|
2016-12-25 07:14:51 +00:00
|
|
|
updateParticle time funct pa = do
|
|
|
|
now <- elapsedTime <$> get
|
|
|
|
if particleCreation pa + particleTimeToLive pa < now
|
2016-12-24 07:27:47 +00:00
|
|
|
then do
|
2017-02-17 16:15:06 +00:00
|
|
|
mproducer <- liftIO $ G.gegl_node_get_producer
|
|
|
|
(particleStackCont pa)
|
|
|
|
"input"
|
|
|
|
case mproducer of
|
|
|
|
Just (producer, padname) -> do
|
|
|
|
consumers <- liftIO $ G.gegl_node_get_consumers
|
|
|
|
(particleStackCont pa)
|
|
|
|
"output"
|
|
|
|
liftIO $ mapM_ (\(node, inpad)-> G.gegl_node_connect_to
|
|
|
|
producer
|
|
|
|
padname
|
|
|
|
node
|
|
|
|
inpad
|
|
|
|
) consumers
|
|
|
|
Nothing -> return ()
|
2016-12-24 07:27:47 +00:00
|
|
|
liftIO $ G.gegl_node_drop $ particleRootNode pa
|
2016-12-25 07:14:51 +00:00
|
|
|
return $ Nothing
|
2016-12-24 07:27:47 +00:00
|
|
|
else do
|
2016-12-25 07:14:51 +00:00
|
|
|
np <- Just <$> funct time pa
|
|
|
|
return $ np
|
|
|
|
-- updateParticle time funct acc@[p] pa = do
|
|
|
|
-- now <- elapsedTime <$> get
|
|
|
|
-- if particleCreation pa + particleTimeToLive pa > now
|
|
|
|
-- then do
|
|
|
|
-- liftIO $ G.gegl_node_drop $ particleRootNode pa
|
|
|
|
-- return $ Nothing : acc
|
|
|
|
-- else do
|
|
|
|
-- when (not $ isNothing p) $ do
|
|
|
|
-- -- liftIO $ traceIO "linking second node in list"
|
|
|
|
-- liftIO $ G.gegl_node_link
|
|
|
|
-- (particleStackCont pa)
|
|
|
|
-- (particleStackCont $ fromJust p)
|
|
|
|
-- np <- Just <$> funct time pa
|
|
|
|
-- return $ np : acc
|
|
|
|
-- updateParticle time funct acc@(p:ps) pa = do
|
|
|
|
-- now <- elapsedTime <$> get
|
|
|
|
-- if particleCreation pa + particleTimeToLive pa > now
|
|
|
|
-- then do
|
|
|
|
-- liftIO $ G.gegl_node_drop $ particleRootNode pa
|
|
|
|
-- return $ Nothing : acc
|
|
|
|
-- else do
|
|
|
|
-- when (isNothing p) $ do
|
|
|
|
-- let mnl = nextLiving ps
|
|
|
|
-- maybe
|
|
|
|
-- (return ())
|
|
|
|
-- (\nl -> do
|
|
|
|
-- -- liftIO $ traceIO "linking nth node on list"
|
|
|
|
-- liftIO $ G.gegl_node_link (particleStackCont pa) (particleStackCont nl))
|
|
|
|
-- mnl
|
|
|
|
-- np <- Just <$> funct time pa
|
|
|
|
-- return $ np : acc
|
2016-12-24 07:27:47 +00:00
|
|
|
|
|
|
|
-- | Get the next living particle from a list
|
|
|
|
nextLiving
|
|
|
|
:: [Maybe Particle]
|
|
|
|
-> Maybe Particle
|
|
|
|
nextLiving [] = Nothing
|
|
|
|
nextLiving acc = case catMaybes acc of
|
|
|
|
[] -> Nothing
|
|
|
|
ps -> Just $ head $ ps
|
|
|
|
-- if isNothing p
|
|
|
|
-- then nextLiving ps
|
|
|
|
-- else p
|
2016-12-12 02:34:57 +00:00
|
|
|
|
|
|
|
drawParticles
|
|
|
|
:: (Particle -> Affection us ())
|
|
|
|
-> [Particle]
|
|
|
|
-> Affection us ()
|
|
|
|
drawParticles = mapM_
|
2016-12-13 10:08:49 +00:00
|
|
|
|
|
|
|
updateParticleSystem
|
|
|
|
:: ParticleSystem
|
|
|
|
-> Double
|
2016-12-24 00:13:00 +00:00
|
|
|
-> (Double -> Particle -> Affection us Particle)
|
2016-12-13 10:08:49 +00:00
|
|
|
-> (G.GeglBuffer -> G.GeglNode -> Particle -> Affection us ())
|
|
|
|
-> Affection us ParticleSystem
|
|
|
|
updateParticleSystem sys sec upd draw = do
|
2017-02-25 16:23:28 +00:00
|
|
|
!x <- catMaybes <$> mapM (updateParticle sec upd) (partStorList $ partSysParts sys)
|
2017-02-22 17:03:16 +00:00
|
|
|
-- liftIO $ traceIO $ show $ length x
|
2016-12-25 07:14:51 +00:00
|
|
|
-- x <- catMaybes <$> foldM (updateParticle sec upd) [] (reverse $ psParts sys)
|
2017-02-22 17:03:16 +00:00
|
|
|
if (not $ null x)
|
|
|
|
then do
|
|
|
|
-- liftIO $ G.gegl_node_link_many $ map particleStackCont (partStorList $ partSysParts sys)
|
|
|
|
-- liftIO $ traceIO "linking last node to output"
|
|
|
|
liftIO $ G.gegl_node_link (particleStackCont $ head x) (partSysNode sys)
|
|
|
|
mapM_ (draw (partSysBuffer sys) (partSysNode sys)) x
|
2017-02-25 16:23:28 +00:00
|
|
|
return sys
|
2017-02-22 17:03:16 +00:00
|
|
|
{ partSysParts = (partSysParts sys)
|
|
|
|
{ partStorList = x
|
|
|
|
}
|
|
|
|
}
|
2017-02-25 16:23:28 +00:00
|
|
|
else do
|
|
|
|
_ <- liftIO $ G.gegl_node_disconnect (partSysNode sys) "input"
|
2017-02-22 17:03:16 +00:00
|
|
|
return sys
|
2017-02-25 16:23:28 +00:00
|
|
|
{ partSysParts = ParticleStorage
|
|
|
|
{ partStorList = []
|
|
|
|
, partStorLatest = Nothing
|
|
|
|
}
|
|
|
|
}
|
2016-12-25 07:14:51 +00:00
|
|
|
|
|
|
|
-- | Function for inserting a new 'Particle' into its 'PartileSystem'
|
|
|
|
insertParticle
|
|
|
|
:: ParticleSystem -- ^ 'ParticleSystem' to insert into
|
|
|
|
-> Particle -- ^ 'Particle' to insert
|
|
|
|
-> Affection us ParticleSystem -- ^ resulting new 'ParticleSystem'
|
|
|
|
insertParticle ps p = do
|
|
|
|
now <- elapsedTime <$> get
|
|
|
|
let newList = chronoInsert now (partStorList $ partSysParts ps) p
|
2017-02-17 16:15:06 +00:00
|
|
|
liftIO $ G.gegl_node_link_many (reverse $ map particleStackCont newList)
|
|
|
|
-- when (not $ isNothing $ partStorLatest $ partSysParts ps) $
|
|
|
|
-- liftIO $ G.gegl_node_link
|
|
|
|
-- (particleStackCont p)
|
|
|
|
-- (particleStackCont $ fromJust $ partStorLatest $ partSysParts ps)
|
2016-12-25 07:14:51 +00:00
|
|
|
return $ ps
|
|
|
|
{ partSysParts = (partSysParts ps)
|
|
|
|
{ partStorLatest = Just p
|
|
|
|
, partStorList = newList
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
|
|
|
-- | Insert a 'Particle' into its chronologically ordered list
|
|
|
|
chronoInsert
|
|
|
|
:: Double -- ^ Time in seconds from beginning of program execution
|
|
|
|
-> [Particle] -- ^ List to insert to
|
|
|
|
-> Particle -- ^ 'Particle' to insert
|
|
|
|
-> [Particle] -- ^ Resulting list
|
|
|
|
chronoInsert now [] np = [np]
|
|
|
|
chronoInsert now [p] np =
|
2017-02-17 16:15:06 +00:00
|
|
|
if now + particleTimeToLive p < (particleCreation np + particleTimeToLive np)
|
2016-12-25 07:14:51 +00:00
|
|
|
then p : [np]
|
|
|
|
else np : [p]
|
|
|
|
chronoInsert now l@(p:ps) np =
|
2017-02-17 16:15:06 +00:00
|
|
|
if now + particleTimeToLive p < (particleCreation np + particleTimeToLive np)
|
2016-12-25 07:14:51 +00:00
|
|
|
then p : chronoInsert now ps np
|
|
|
|
else np : l
|