Grid Proto
Game Engine for Prototyping on a Grid
Quickly prototype a graphical program with basic input, colors, shapes, and text.
Grid Proto follows an 'anti-polished' philosophy. It exposes a heavily limited API over SDL2 which doesn't allow for any user media.
No images, fonts, or audio can be loaded.
This usage is one step above prototyping within the terminal. So, just write a function for updating state, a pure function for rendering, and a pure function for sound effects.
Hello World
import GridProto
main :: IO ()
main = runGridProto helloWorld ()
helloWorld :: GridProto ()
helloWorld = defaultGridProto
{ title = "Hello World"
, viewFn = \_ ->
drawString wh1 (0,0) "hello" <> drawString wh1 (0,1) "world"
}
API
data GridProto state = GridProto
{ title :: String
, rows :: Int
, cols :: Int
, tilePixelSize :: Int
, backgroundColor :: Color
, updateFn :: Input -> state -> IO (state, [String])
, viewFn :: state -> View
, sfxFn :: state -> [Sfx]
, quitFn :: state -> Bool
}
defaultGridProto :: GridProto s
runGridProto
:: GridProto s
-> s
-> IO ()
type View = Map (Int, Int) Tile
emptyView :: View
data Tile = Tile
{ symbol :: Maybe (Char, Color)
, shape :: Maybe (Shape, Color)
, fill :: Maybe Color
}
data Color
rd0, rd1, rd2
or0, or1, or2
yw0, yw1, yw2
ch0, ch1, ch2
gn0, gn1, gn2
sp0, sp1, sp2
cn0, cn1, cn2
az0, az1, az2
bu0, bu1, bu2
vt0, vt1, vt2
mg0, mg1, mg2
rs0, rs1, rs2
br0, br1, br2
gy0, gy1, gy2
wh0, wh1, wh2
bk0, bk1, bk2
data Shape
= Circle | FillCircle
| Triangle | FillTriangle
| Square | FillSquare
| Plus | Dash
| Bar | Cross
drawString :: Color -> (Int, Int) -> String -> View
drawTile :: View -> (Int, Int) -> Tile -> View
drawView :: View -> (Int, Int) -> View -> View
mergeViews :: View -> View -> View
rainbow, warms, cools, colorWheel0, colorWheel1, colorWheel2 :: [Color]
shade, tint :: Color -> Color
data Viewport = Viewport
{ vpView :: View
, vpXY :: (Int, Int)
, vpDim :: (Int, Int)
}
mergeViewport :: View -> Viewport -> View
mergeViewports :: View -> [Viewport] -> View
mapTile :: MapTile a
=> ((Char, Color) -> (Char, Color)) -> ((Shape, Color) -> (Shape, Color))
-> (Color -> Color) -> a -> a
mapSymbol :: MapTile a => ((Char, Color) -> (Char, Color)) -> a -> a
mapShape :: MapTile a => ((Shape, Color) -> (Shape, Color)) -> a -> a
mapFill :: MapTile a => (Color -> Color) -> a -> a
data Input = Input
{ mouse :: Mouse, keys :: Keys
, controller1, controller2, controller3, controller4 :: Controller
}
data Key
= Char Char
| UpArrow | DownArrow | LeftArrow | RightArrow
| Enter | Escape
| LeftShift | RightShift | LeftControl | RightControl
| LeftAlt | RightAlt
| Tab | Backspace | Meta
data KeyState = Pressed | Held | Released | Untouched
newtype Keys
lookupKey :: Keys -> Key -> KeyState
data Mouse = Mouse { mousePosition :: (Int, Int), mouseButton :: KeyState }
data Controller = Controller
{ isConnected :: Bool
, startButton, backButton :: KeyState
, dpadUp, dpadDown, dpadLeft, dpadRight :: KeyState
, aButton, bButton, xButton, yButton :: KeyState
, leftStick , rightStick :: KeyState
, leftShoulder, rightShoulder :: KeyState
, leftAxis, rightAxis :: Axis
}
data Axis = Axis { xAxis :: Float, yAxis :: Float }
data Sfx
= SfxSuccess | SfxBell | SfxSelect
| SfxNoSelect | SfxScroll | SfxChimes
| SfxLaser | SfxPowerUp | SfxJump
| SfxDamage | SfxExplosion | SfxNoise