Skip to content

Instantly share code, notes, and snippets.

@myuon
Created December 4, 2013 14:21
Show Gist options
  • Save myuon/7788176 to your computer and use it in GitHub Desktop.
Save myuon/7788176 to your computer and use it in GitHub Desktop.
同じ型を持つオブジェクトの実装を変えられるようにしたい ref: http://qiita.com/myuon_myon/items/38dc54565a37597ecf7e
{-# LANGUAGE TemplateHaskell, TypeSynonymInstances, FlexibleInstances #-}
import Control.Monad.State
import Control.Lens
import Data.Functor.Identity
data Autonomie m a = Autonomie { auto :: a, runAuto :: m () }
class Game c where
update :: State c ()
draw :: StateT c IO ()
data Object = Object { _pos :: (Int, Int) }
makeClassy ''Object
type Character = Autonomie (State Object) Object
instance HasObject Character where
object = lens auto (\f a -> Autonomie a (runAuto f))
instance Game Character where
update = do
f <- get
object %= execState (runAuto f)
draw = do
f <- get
lift $ print $ f^.pos
walk :: State Object ()
walk = pos %= (\(x,y) -> (x+2, y))
dash :: State Object ()
dash = pos %= (\(x,y) -> (x+10, y))
main = do
let chara1 = Autonomie (Object (100, 100)) walk
draw `execStateT` (update `execState` chara1)
let chara2 = Autonomie (Object (100, 100)) dash
draw `execStateT` (update `execState` chara2)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment