LoginSignup
1
1

More than 5 years have passed since last update.

同じ型を持つオブジェクトの実装を変えられるようにしたい

Posted at

自律機能を備えたAutonomie
Characterを生成するときにどうやって動くか(runAuto の実装)を選ぶことができる

キャラクタによってmoveの実装をわけたいときなどに便利(おそらくもう少し一般化可能)

{-# 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)
1
1
0

Register as a new user and use Qiita more conveniently

  1. You get articles that match your needs
  2. You can efficiently read back useful information
  3. You can use dark theme
What you can do with signing up
1
1