affection/src/Affection/Actor.hs
2017-03-21 12:04:56 +01:00

55 lines
1.4 KiB
Haskell

{-# LANGUAGE RecordWildCards #-}
-- | This module implements the Actor, a Datastructure binding a 'G.GeglNode'
-- to a game asset
module Affection.Actor
( Actor(..)
, ActorProperty(..)
, updateProperties
, applyProperties
) where
import qualified GEGL as G
import qualified Data.Map.Strict as M
import Data.List
import qualified Control.Monad.Parallel as MP
import Affection.Types
data Ord a => Actor a = Actor
{ actorProperties :: [ActorProperty a]
, actorNodes :: M.Map a G.GeglNode
}
data Ord a => ActorProperty a = ActorProperty
{ apName :: String
, apValue :: G.PropertyValue
, apMapping :: Maybe a
}
updateProperties :: Ord a => [G.Property] -> Actor a -> Actor a
updateProperties ps act@Actor{..} =
act
{ actorProperties =
foldl (\acc (G.Property name val) -> newProp name val acc) actorProperties ps
}
where
newProp name val acc = nubBy (\a b -> apName a == apName b) $ (getProp name)
{ apValue = val
} : acc
getProp n = getProp' n actorProperties
getProp' n [] = error $ "no ActorProperty found: " ++ n
getProp' n (p:ps)
| apName p == n = p
| otherwise = getProp' n ps
applyProperties :: Ord a => Actor a -> Affection us ()
applyProperties Actor{..} =
MP.mapM_ (\(ActorProperty{..}) ->
maybe (return ()) (\m ->
liftIO $ G.gegl_node_set (actorNodes M.! m) $ G.Operation "" $
(G.Property apName apValue) : []
) apMapping
) actorProperties