introducing actors

This commit is contained in:
nek0 2017-03-18 17:38:26 +01:00
parent a5273ff79b
commit 6eccf8ed5b
5 changed files with 48 additions and 10 deletions

View file

@ -42,6 +42,7 @@ library
, Affection.StateMachine , Affection.StateMachine
, Affection.MouseInteractable , Affection.MouseInteractable
, Affection.Property , Affection.Property
, Affection.Actor
default-extensions: OverloadedStrings default-extensions: OverloadedStrings
-- Modules included in this library but not exported. -- Modules included in this library but not exported.

View file

@ -25,6 +25,7 @@ main = do
data UserData = UserData data UserData = UserData
{ nodeGraph :: M.Map String G.GeglNode { nodeGraph :: M.Map String G.GeglNode
, actors :: M.Map String Actor
, foreground :: G.GeglBuffer , foreground :: G.GeglBuffer
, lastTick :: Double , lastTick :: Double
} }
@ -47,13 +48,14 @@ load _ = do
props $ props $
prop "buffer" buffer prop "buffer" buffer
traceM "buffer-sink" traceM "buffer-sink"
rect <- G.gegl_node_new_child root $ G.Operation "gegl:rectangle" $ rectProps <- return $
props $ do props $ do
prop "x" (0::Double) prop "x" (0::Double)
prop "y" (0::Double) prop "y" (0::Double)
prop "width" (20::Double) prop "width" (20::Double)
prop "height" (20::Double) prop "height" (20::Double)
prop "color" $ G.RGBA 1 0 0 0.5 prop "color" $ G.RGBA 1 0 0 0.5
rect <- G.gegl_node_new_child root $ G.Operation "gegl:rectangle" rectProps
traceM "rect" traceM "rect"
crop <- G.gegl_node_new_child root $ G.Operation "gegl:crop" $ crop <- G.gegl_node_new_child root $ G.Operation "gegl:crop" $
props $ do props $ do
@ -61,6 +63,7 @@ load _ = do
prop "height" (600::Double) prop "height" (600::Double)
G.gegl_node_link_many [checkerboard, over, crop, sink] G.gegl_node_link_many [checkerboard, over, crop, sink]
_ <- G.gegl_node_connect_to rect "output" over "aux" _ <- G.gegl_node_connect_to rect "output" over "aux"
let rectActor = Actor rectProps rect
traceM "connections made" traceM "connections made"
myMap <- return $ M.fromList myMap <- return $ M.fromList
[ ("root" , root) [ ("root" , root)
@ -71,8 +74,12 @@ load _ = do
, ("crop" , crop) , ("crop" , crop)
] ]
traceM "loading complete" traceM "loading complete"
actorMap <- return $ M.fromList
[ ("rect", rectActor)
]
return $ UserData return $ UserData
{ nodeGraph = myMap { nodeGraph = myMap
, actors = actorMap
, foreground = buffer , foreground = buffer
, lastTick = 0 , lastTick = 0
} }
@ -85,6 +92,7 @@ load _ = do
draw :: Affection UserData () draw :: Affection UserData ()
draw = do draw = do
UserData{..} <- getAffection UserData{..} <- getAffection
mapM_ (\(Actor ps node) -> liftIO $ G.gegl_node_set node $ G.Operation "" ps) actors
process (nodeGraph M.! "sink") process (nodeGraph M.! "sink")
present (GeglRectangle 0 0 800 600) foreground True present (GeglRectangle 0 0 800 600) foreground True
@ -104,10 +112,23 @@ handle :: SDL.EventPayload -> Affection UserData ()
handle (SDL.MouseMotionEvent dat) = do handle (SDL.MouseMotionEvent dat) = do
let (SDL.P (SDL.V2 x y)) = SDL.mouseMotionEventPos dat let (SDL.P (SDL.V2 x y)) = SDL.mouseMotionEventPos dat
ud <- getAffection ud <- getAffection
liftIO $ G.gegl_node_set (nodeGraph ud M.! "rect") $ G.Operation "" $
props $ do nmap <- return $ M.adjust
prop "x" (fromIntegral (x - 10) :: Double) (\a -> Actor (props $ do
prop "y" $ (fromIntegral (y - 10) :: Double) prop "y" (fromIntegral (y - 10) :: Double)
prop "x" (fromIntegral (x - 10) :: Double)
)
(actorNode a)
)
"rect"
(actors ud)
putAffection ud
{ actors = nmap
}
-- liftIO $ G.gegl_node_set (nodeGraph ud M.! "rect") $ G.Operation "" $
-- props $ do
-- prop "x" (fromIntegral (x - 10) :: Double)
-- prop "y" $ (fromIntegral (y - 10) :: Double)
handle (SDL.WindowClosedEvent _) = do handle (SDL.WindowClosedEvent _) = do
traceM "seeya!" traceM "seeya!"

View file

@ -13,7 +13,6 @@ module Affection
, getDelta , getDelta
, quit , quit
, module A , module A
, module Affection.Property
) where ) where
import qualified SDL import qualified SDL
@ -39,7 +38,8 @@ import Affection.Draw as A
import Affection.Particle as A import Affection.Particle as A
import Affection.StateMachine as A import Affection.StateMachine as A
import Affection.MouseInteractable as A import Affection.MouseInteractable as A
import Affection.Property import Affection.Property as A
import Affection.Actor as A
import qualified BABL as B import qualified BABL as B

12
src/Affection/Actor.hs Normal file
View file

@ -0,0 +1,12 @@
-- | This module implements the Actor, a Datastructure binding a 'G.GeglNode'
-- to a game asset
module Affection.Actor
( Actor(..)
) where
import qualified GEGL as G
data Actor = Actor
{ actorProperties :: [G.Property]
, actorNode :: G.GeglNode
}

View file

@ -1,10 +1,15 @@
{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleInstances #-}
module Affection.Property where module Affection.Property
( Props(..)
, prop
, props
) where
import Control.Monad.State.Lazy
import qualified GEGL as G import qualified GEGL as G
import qualified BABL as B import qualified BABL as B
import Control.Monad.State.Lazy
import Foreign.Ptr (Ptr) import Foreign.Ptr (Ptr)
type Props a = State [G.Property] a type Props a = State [G.Property] a
@ -34,7 +39,6 @@ instance IsPropertyValue G.Color where
instance IsPropertyValue B.PixelFormat where instance IsPropertyValue B.PixelFormat where
toPropertyValue = G.PropertyFormat toPropertyValue = G.PropertyFormat
instance IsPropertyValue G.GeglBuffer where instance IsPropertyValue G.GeglBuffer where
toPropertyValue = G.PropertyBuffer toPropertyValue = G.PropertyBuffer