fixed routing
This commit is contained in:
parent
428ab736f8
commit
2095bb1924
4 changed files with 149 additions and 71 deletions
|
@ -75,7 +75,7 @@ load _ = do
|
||||||
return $ UserData
|
return $ UserData
|
||||||
{ nodeGraph = myMap
|
{ nodeGraph = myMap
|
||||||
, foreground = buffer
|
, foreground = buffer
|
||||||
, partsys = ParticleSystem [] nop buffer
|
, partsys = ParticleSystem (ParticleStorage Nothing []) nop buffer
|
||||||
}
|
}
|
||||||
|
|
||||||
drawInit :: Affection UserData ()
|
drawInit :: Affection UserData ()
|
||||||
|
@ -138,10 +138,10 @@ update sec = do
|
||||||
liftIO $ G.gegl_node_connect_to tempRect "output" tempOver "aux"
|
liftIO $ G.gegl_node_connect_to tempRect "output" tempOver "aux"
|
||||||
-- traceM $ "position is: " ++ show x ++ " " ++ show y
|
-- traceM $ "position is: " ++ show x ++ " " ++ show y
|
||||||
-- traceM $ "velocity is: " ++ show vx ++ " " ++ show vy
|
-- traceM $ "velocity is: " ++ show vx ++ " " ++ show vy
|
||||||
putAffection $ ud
|
ips <- insertParticle (partsys ud) $
|
||||||
{ partsys = (partsys ud)
|
Particle
|
||||||
{ psParts = (Particle
|
{ particleTimeToLive = life
|
||||||
{ particleLife = life
|
, particleCreation = elapsedTime ad
|
||||||
, particlePosition = (fromIntegral x, fromIntegral y)
|
, particlePosition = (fromIntegral x, fromIntegral y)
|
||||||
, particleRotation = Rad 0
|
, particleRotation = Rad 0
|
||||||
, particleVelocity = (vx, vy)
|
, particleVelocity = (vx, vy)
|
||||||
|
@ -154,13 +154,14 @@ update sec = do
|
||||||
]
|
]
|
||||||
, particleStackCont = tempOver
|
, particleStackCont = tempOver
|
||||||
, particleDrawFlange = tempOver
|
, particleDrawFlange = tempOver
|
||||||
}) : (psParts $ partsys ud)
|
|
||||||
}
|
}
|
||||||
|
putAffection $ ud
|
||||||
|
{ partsys = ips
|
||||||
}
|
}
|
||||||
when (not $ null $ psParts $ partsys ud) $
|
-- when (not $ null $ psParts $ partsys ud) $
|
||||||
liftIO $ G.gegl_node_link
|
-- liftIO $ G.gegl_node_link
|
||||||
tempOver
|
-- tempOver
|
||||||
(particleStackCont $ head $ psParts $ partsys ud)
|
-- (particleStackCont $ head $ psParts $ partsys ud)
|
||||||
else
|
else
|
||||||
return ()
|
return ()
|
||||||
SDL.WindowClosedEvent _ -> do
|
SDL.WindowClosedEvent _ -> do
|
||||||
|
|
|
@ -65,6 +65,7 @@ withAffection AffectionConfig{..} = do
|
||||||
, drawSurface = surface
|
, drawSurface = surface
|
||||||
, drawFormat = format
|
, drawFormat = format
|
||||||
, drawStack = []
|
, drawStack = []
|
||||||
|
, elapsedTime = 0
|
||||||
}) <$> loadState surface
|
}) <$> loadState surface
|
||||||
(_, nState) <- runStateT ( A.runState $ do
|
(_, nState) <- runStateT ( A.runState $ do
|
||||||
preLoop
|
preLoop
|
||||||
|
@ -81,11 +82,14 @@ withAffection AffectionConfig{..} = do
|
||||||
ad <- get
|
ad <- get
|
||||||
-- clean draw requests from last run
|
-- clean draw requests from last run
|
||||||
mapM_ (invalidateDrawRequest pixels stride cpp) $ drawStack ad
|
mapM_ (invalidateDrawRequest pixels stride cpp) $ drawStack ad
|
||||||
|
-- compute dt and update elapsedTime
|
||||||
|
let dt = (fromIntegral $ toNanoSecs $ diffTimeSpec lastTime now) / (fromIntegral 10 ^ 9)
|
||||||
put $ ad
|
put $ ad
|
||||||
{ drawStack = [] }
|
{ drawStack = []
|
||||||
|
, elapsedTime = elapsedTime ad + dt
|
||||||
|
}
|
||||||
-- execute user defined update loop
|
-- execute user defined update loop
|
||||||
updateLoop $ (fromIntegral $ toNanoSecs $ diffTimeSpec lastTime now) /
|
updateLoop dt
|
||||||
(fromIntegral 10 ^ 9)
|
|
||||||
-- execute user defined draw loop
|
-- execute user defined draw loop
|
||||||
drawLoop
|
drawLoop
|
||||||
-- handle all new draw requests
|
-- handle all new draw requests
|
||||||
|
|
|
@ -5,11 +5,13 @@ module Affection.Particle
|
||||||
( updateParticle
|
( updateParticle
|
||||||
, drawParticles
|
, drawParticles
|
||||||
, updateParticleSystem
|
, updateParticleSystem
|
||||||
|
, insertParticle
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Affection.Types
|
import Affection.Types
|
||||||
|
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
|
import Control.Monad.State (get)
|
||||||
|
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
|
|
||||||
|
@ -27,48 +29,67 @@ updateParticle
|
||||||
-- ^ Update function for a single 'Particle'
|
-- ^ Update function for a single 'Particle'
|
||||||
-- This Function should take the elapsed time
|
-- This Function should take the elapsed time
|
||||||
-- in seconds and the initial particle as arguments.
|
-- in seconds and the initial particle as arguments.
|
||||||
-> [Maybe Particle]
|
-- -> [Maybe Particle]
|
||||||
-> Particle
|
-> Particle
|
||||||
-- ^ 'Particle' to be processed
|
-- ^ 'Particle' to be processed
|
||||||
-> Affection us [Maybe Particle]
|
-- -> Affection us [Maybe Particle]
|
||||||
|
-> Affection us (Maybe Particle)
|
||||||
-- ^ resulting 'Particle'
|
-- ^ resulting 'Particle'
|
||||||
updateParticle time funct acc@[] pa =
|
updateParticle time funct pa = do
|
||||||
if particleLife pa - time < 0
|
now <- elapsedTime <$> get
|
||||||
|
if particleCreation pa + particleTimeToLive pa < now
|
||||||
then do
|
then do
|
||||||
liftIO $ G.gegl_node_drop $ particleRootNode pa
|
mproducer <- liftIO $ G.gegl_node_get_producer
|
||||||
return $ Nothing : acc
|
|
||||||
else do
|
|
||||||
np <- Just <$> funct time pa { particleLife = particleLife pa - time }
|
|
||||||
return $ np : acc
|
|
||||||
updateParticle time funct acc@[p] pa =
|
|
||||||
if particleLife pa - time < 0
|
|
||||||
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 pa)
|
||||||
(particleStackCont $ fromJust p)
|
"input"
|
||||||
np <- Just <$> funct time pa { particleLife = particleLife pa - time }
|
case mproducer of
|
||||||
return $ np : acc
|
Just (producer, padname) -> do
|
||||||
updateParticle time funct acc@(p:ps) pa =
|
consumers <- liftIO $ G.gegl_node_get_consumers
|
||||||
if particleLife pa - time < 0
|
(particleStackCont pa)
|
||||||
then do
|
"output"
|
||||||
|
liftIO $ mapM_ (\(node, inpad)-> G.gegl_node_connect_to
|
||||||
|
producer
|
||||||
|
padname
|
||||||
|
node
|
||||||
|
inpad
|
||||||
|
) consumers
|
||||||
|
Nothing -> return ()
|
||||||
liftIO $ G.gegl_node_drop $ particleRootNode pa
|
liftIO $ G.gegl_node_drop $ particleRootNode pa
|
||||||
return $ Nothing : acc
|
return $ Nothing
|
||||||
else do
|
else do
|
||||||
when (isNothing p) $ do
|
np <- Just <$> funct time pa
|
||||||
let mnl = nextLiving ps
|
return $ np
|
||||||
maybe
|
-- updateParticle time funct acc@[p] pa = do
|
||||||
(return ())
|
-- now <- elapsedTime <$> get
|
||||||
(\nl -> do
|
-- if particleCreation pa + particleTimeToLive pa > now
|
||||||
-- liftIO $ traceIO "linking nth node on list"
|
-- then do
|
||||||
liftIO $ G.gegl_node_link (particleStackCont pa) (particleStackCont nl))
|
-- liftIO $ G.gegl_node_drop $ particleRootNode pa
|
||||||
mnl
|
-- return $ Nothing : acc
|
||||||
np <- Just <$> funct time pa { particleLife = particleLife pa - time }
|
-- else do
|
||||||
return $ np : acc
|
-- 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
|
||||||
|
|
||||||
-- | Get the next living particle from a list
|
-- | Get the next living particle from a list
|
||||||
nextLiving
|
nextLiving
|
||||||
|
@ -95,12 +116,53 @@ updateParticleSystem
|
||||||
-> (G.GeglBuffer -> G.GeglNode -> Particle -> Affection us ())
|
-> (G.GeglBuffer -> G.GeglNode -> Particle -> Affection us ())
|
||||||
-> Affection us ParticleSystem
|
-> Affection us ParticleSystem
|
||||||
updateParticleSystem sys sec upd draw = do
|
updateParticleSystem sys sec upd draw = do
|
||||||
-- let x = catMaybes <$> mapM (updateParticle sec upd) (psParts sys)
|
x <- catMaybes <$> mapM (updateParticle sec upd) (partStorList $ partSysParts sys)
|
||||||
-- x <- liftIO $ catMaybes <$> foldM (updateParticle sec upd) [] (psParts sys)
|
-- x <- catMaybes <$> foldM (updateParticle sec upd) [] (reverse $ psParts sys)
|
||||||
x <- catMaybes <$> foldM (updateParticle sec upd) [] (reverse $ psParts sys)
|
|
||||||
when (not $ null x) $ do
|
when (not $ null x) $ do
|
||||||
-- liftIO $ traceIO "linking last node to output"
|
-- liftIO $ traceIO "linking last node to output"
|
||||||
liftIO $ G.gegl_node_link (particleStackCont $ last x) (psNode sys)
|
liftIO $ G.gegl_node_link (particleStackCont $ last x) (partSysNode sys)
|
||||||
mapM_ (draw (psBuffer sys) (psNode sys)) x
|
mapM_ (draw (partSysBuffer sys) (partSysNode sys)) x
|
||||||
return $ sys
|
return $ sys
|
||||||
{ psParts = x }
|
{ partSysParts = (partSysParts sys)
|
||||||
|
{ partStorList = x
|
||||||
|
, partStorLatest =
|
||||||
|
if null x
|
||||||
|
then Nothing
|
||||||
|
else partStorLatest (partSysParts sys)
|
||||||
|
}
|
||||||
|
}
|
||||||
|
|
||||||
|
-- | 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
|
||||||
|
when (not $ isNothing $ partStorLatest $ partSysParts ps) $
|
||||||
|
liftIO $ G.gegl_node_link
|
||||||
|
(particleStackCont p)
|
||||||
|
(particleStackCont $ fromJust $ partStorLatest $ partSysParts ps)
|
||||||
|
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 =
|
||||||
|
if now + particleTimeToLive p < particleCreation np
|
||||||
|
then p : [np]
|
||||||
|
else np : [p]
|
||||||
|
chronoInsert now l@(p:ps) np =
|
||||||
|
if now + particleTimeToLive p < particleCreation np
|
||||||
|
then p : chronoInsert now ps np
|
||||||
|
else np : l
|
||||||
|
|
|
@ -19,6 +19,7 @@ module Affection.Types
|
||||||
-- | Particle system
|
-- | Particle system
|
||||||
, Particle(..)
|
, Particle(..)
|
||||||
, ParticleSystem(..)
|
, ParticleSystem(..)
|
||||||
|
, ParticleStorage(..)
|
||||||
-- | Convenience exports
|
-- | Convenience exports
|
||||||
, liftIO
|
, liftIO
|
||||||
, SDL.WindowConfig(..)
|
, SDL.WindowConfig(..)
|
||||||
|
@ -77,6 +78,7 @@ data AffectionData us = AffectionData
|
||||||
, drawFormat :: B.BablFormatPtr -- ^ Target format
|
, drawFormat :: B.BablFormatPtr -- ^ Target format
|
||||||
, drawStack :: [DrawRequest] -- ^ Stack of 'DrawRequest's to be processed
|
, drawStack :: [DrawRequest] -- ^ Stack of 'DrawRequest's to be processed
|
||||||
, clearStack :: [DrawRequest] -- ^ Stack of 'DrawRequest's to be invalidated
|
, clearStack :: [DrawRequest] -- ^ Stack of 'DrawRequest's to be invalidated
|
||||||
|
, elapsedTime :: Double -- ^ Elapsed time in seconds
|
||||||
}
|
}
|
||||||
|
|
||||||
-- | This datatype stores information about areas of a 'G.GeglBuffer' to be updated
|
-- | This datatype stores information about areas of a 'G.GeglBuffer' to be updated
|
||||||
|
@ -165,8 +167,10 @@ instance Eq Angle where
|
||||||
|
|
||||||
-- | A single particle
|
-- | A single particle
|
||||||
data Particle = Particle
|
data Particle = Particle
|
||||||
{ particleLife :: Double
|
{ particleTimeToLive :: Double
|
||||||
-- ^ Time to live in seconds
|
-- ^ Time to live in seconds
|
||||||
|
, particleCreation :: Double
|
||||||
|
-- ^ Creation time of particle in seconds form program start
|
||||||
, particlePosition :: (Double, Double)
|
, particlePosition :: (Double, Double)
|
||||||
-- ^ Position of particle on canvas
|
-- ^ Position of particle on canvas
|
||||||
, particleRotation :: Angle
|
, particleRotation :: Angle
|
||||||
|
@ -185,8 +189,15 @@ data Particle = Particle
|
||||||
-- ^ 'G.GeglNode' to connect draw actions to
|
-- ^ 'G.GeglNode' to connect draw actions to
|
||||||
}
|
}
|
||||||
|
|
||||||
|
-- | The particle system
|
||||||
data ParticleSystem = ParticleSystem
|
data ParticleSystem = ParticleSystem
|
||||||
{ psParts :: [Particle]
|
{ partSysParts :: ParticleStorage
|
||||||
, psNode :: G.GeglNode
|
, partSysNode :: G.GeglNode
|
||||||
, psBuffer :: G.GeglBuffer
|
, partSysBuffer :: G.GeglBuffer
|
||||||
|
}
|
||||||
|
|
||||||
|
-- | The particle storage datatype
|
||||||
|
data ParticleStorage = ParticleStorage
|
||||||
|
{ partStorLatest :: Maybe Particle -- ^ The particle stored last
|
||||||
|
, partStorList :: [Particle] -- ^ List of particles in ascending order of remaining lifetime
|
||||||
}
|
}
|
||||||
|
|
Loading…
Reference in a new issue