module Brillo.Interface.IO.Interact (
module Brillo.Data.Display,
module Brillo.Data.Picture,
module Brillo.Data.Color,
interactIO,
Controller (..),
Event (..),
Key (..),
SpecialKey (..),
MouseButton (..),
KeyState (..),
Modifiers (..),
)
where
import Brillo.Data.Color
import Brillo.Data.Controller
import Brillo.Data.Display
import Brillo.Data.Picture
import Brillo.Internals.Interface.Backend
import Brillo.Internals.Interface.Event
import Brillo.Internals.Interface.Interact
interactIO
:: Display
-> Color
-> world
-> (world -> IO Picture)
-> (Event -> world -> IO world)
-> (Controller -> IO ())
-> IO ()
interactIO :: forall world.
Display
-> Color
-> world
-> (world -> IO Picture)
-> (Event -> world -> IO world)
-> (Controller -> IO ())
-> IO ()
interactIO Display
dis Color
backColor world
worldInit world -> IO Picture
makePicture Event -> world -> IO world
handleEvent Controller -> IO ()
eatController =
GLFWState
-> Display
-> Color
-> world
-> (world -> IO Picture)
-> (Event -> world -> IO world)
-> (Controller -> IO ())
-> IO ()
forall a world.
Backend a =>
a
-> Display
-> Color
-> world
-> (world -> IO Picture)
-> (Event -> world -> IO world)
-> (Controller -> IO ())
-> IO ()
interactWithBackend
GLFWState
defaultBackendState
Display
dis
Color
backColor
world
worldInit
world -> IO Picture
makePicture
Event -> world -> IO world
handleEvent
Controller -> IO ()
eatController