LoginSignup
2
2

More than 5 years have passed since last update.

free-gameで円を描く!

Last updated at Posted at 2013-01-04

@fumieval さんのお作りになった free-game(http://hackage.haskell.org/package/free-game) というGUIを扱うパッケージの(骨組み)サンプルです。

画面に円を描きます。
(円を描く函数renderCircleはfree-game 3.0では未実装なのでここでは自前で実装しています)

sample.hs
{-# LANGUAGE TemplateHaskell #-}
import Graphics.FreeGame
import Data.Word
import Data.Array.Repa
import Control.Monad

import Control.Lens

data World = World{
  _object :: Picture,
  _pos :: (Float, Float)
  }

$(makeLenses ''World)

initWorld :: Picture ->  World
initWorld p = World { _object = p, _pos = (100,300) }

renderCircle :: Int -> (Word8, Word8, Word8, Word8) -> Bitmap
renderCircle size (r,g,b,a) = toStableBitmap $ computeS $ fromFunction (Z :. size :. size :. 4) render where
    center = fromIntegral size / 2
    render (Z:.y:.x:.0)
        | s < 0 = a
        | s >= 1 = 0
        | otherwise = floor ((1 - s) * 256)
        where
            r = sqrt $ (fromIntegral y - center) ^ 2 + (fromIntegral x - center) ^ 2
            s = r - fromIntegral size / 2
    render (Z:._:._:.c) = [undefined,b,g,r] !! c

draw :: World -> Game ()
draw w = let (x,y) = (w ^. pos) in drawPicture . Translate (Vec2 x y) $ (w ^. object)

main :: IO (Maybe ())
main = runGame defaultGameParam $ do
  p <- loadPicture $ renderCircle 128 (128, 216, 128, 255)
  run $ initWorld p

  where
    run :: World -> Game ()
    run w = do
      isQuit <- askInput KeyEsc

      draw w

      tick
      unless isQuit $ run w

簡単で強力なfree-gameをあなたもぜひ!

2
2
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
2
2