module Graphics.GPipe.Context.GLFW.Calls where
import Control.Monad (when)
import qualified Text.Printf as Text
import qualified Control.Concurrent as Conc
import qualified Graphics.UI.GLFW as GLFW
getCurrentContext :: IO (Maybe GLFW.Window)
getCurrentContext = GLFW.getCurrentContext
debug :: String -> IO ()
debug msg = do
t <- GLFW.getTime
tid <- Conc.myThreadId
c <- getCurrentContext
Text.printf "[%03.3fs, %s has %s]: %s\n" (maybe (0/0) id t) (show tid) (show c) msg
type OnMain a = IO a -> IO a
type EffectMain = IO () -> IO ()
init :: OnMain Bool -> IO Bool
init onMain = onMain GLFW.init
terminate :: EffectMain -> IO ()
terminate onMain = onMain GLFW.terminate
setErrorCallback :: EffectMain -> Maybe GLFW.ErrorCallback -> IO ()
setErrorCallback onMain callbackHuh = onMain $ GLFW.setErrorCallback callbackHuh
createWindow :: OnMain (Maybe GLFW.Window) -> Int -> Int -> String -> Maybe GLFW.Monitor -> [GLFW.WindowHint] -> Maybe GLFW.Window -> IO (Maybe GLFW.Window)
createWindow onMain width height title monitor hints parent = onMain $ do
GLFW.defaultWindowHints
mapM_ GLFW.windowHint hints
GLFW.createWindow width height title monitor parent
destroyWindow :: EffectMain -> GLFW.Window -> IO ()
destroyWindow onMain window = onMain $ GLFW.destroyWindow window
windowHints :: EffectMain -> [GLFW.WindowHint] -> IO ()
windowHints onMain hints = onMain $ GLFW.defaultWindowHints >> mapM_ GLFW.windowHint hints
makeContextCurrent :: String -> Maybe GLFW.Window -> IO ()
makeContextCurrent reason windowHuh = do
ccHuh <- getCurrentContext
when (ccHuh /= windowHuh) $ do
debug $ Text.printf "attaching %s, reason: %s" (show windowHuh) reason
GLFW.makeContextCurrent windowHuh
swapInterval :: Int -> IO ()
swapInterval interval = GLFW.swapInterval interval
swapBuffers :: GLFW.Window -> IO ()
swapBuffers window = GLFW.swapBuffers window
waitEvents :: EffectMain -> IO ()
waitEvents onMain = onMain GLFW.waitEvents
pollEvents :: EffectMain -> IO ()
pollEvents onMain = onMain GLFW.pollEvents
postEmptyEvent :: IO ()
postEmptyEvent = GLFW.postEmptyEvent
windowShouldClose :: GLFW.Window -> IO Bool
windowShouldClose window = GLFW.windowShouldClose window
setWindowShouldClose :: GLFW.Window -> Bool -> IO ()
setWindowShouldClose window bool = GLFW.setWindowShouldClose window bool
setWindowCloseCallback :: EffectMain -> GLFW.Window -> Maybe GLFW.WindowCloseCallback -> IO ()
setWindowCloseCallback onMain window cb = onMain $ GLFW.setWindowCloseCallback window cb
getFramebufferSize :: OnMain (Int, Int) -> GLFW.Window -> IO (Int, Int)
getFramebufferSize onMain window = onMain $ GLFW.getFramebufferSize window
setKeyCallback :: EffectMain -> GLFW.Window -> Maybe GLFW.KeyCallback -> IO ()
setKeyCallback onMain window cb = onMain $ GLFW.setKeyCallback window cb
getKey :: OnMain GLFW.KeyState -> GLFW.Window -> GLFW.Key -> IO GLFW.KeyState
getKey onMain window key = onMain $ GLFW.getKey window key
setStickyKeysInputMode :: EffectMain -> GLFW.Window -> GLFW.StickyKeysInputMode -> IO ()
setStickyKeysInputMode onMain window mode = onMain $ GLFW.setStickyKeysInputMode window mode
getStickyKeysInputMode :: OnMain GLFW.StickyKeysInputMode -> GLFW.Window -> IO GLFW.StickyKeysInputMode
getStickyKeysInputMode onMain window = onMain $ GLFW.getStickyKeysInputMode window
setCharCallback :: EffectMain -> GLFW.Window -> Maybe GLFW.CharCallback -> IO ()
setCharCallback onMain window cb = onMain $ GLFW.setCharCallback window cb
setCursorPosCallback :: EffectMain -> GLFW.Window -> Maybe GLFW.CursorPosCallback -> IO ()
setCursorPosCallback onMain window cb = onMain $ GLFW.setCursorPosCallback window cb
getCursorPos :: OnMain (Double, Double) -> GLFW.Window -> IO (Double, Double)
getCursorPos onMain window = onMain $ GLFW.getCursorPos window
setCursorInputMode :: EffectMain -> GLFW.Window -> GLFW.CursorInputMode -> IO ()
setCursorInputMode onMain window mode = onMain $ GLFW.setCursorInputMode window mode
getCursorInputMode :: OnMain GLFW.CursorInputMode -> GLFW.Window -> IO GLFW.CursorInputMode
getCursorInputMode onMain window = onMain $ GLFW.getCursorInputMode window
setCursor :: EffectMain -> GLFW.Window -> GLFW.Cursor -> IO ()
setCursor onMain window cursor = onMain $ GLFW.setCursor window cursor
setCursorEnterCallback :: EffectMain -> GLFW.Window -> Maybe GLFW.CursorEnterCallback -> IO ()
setCursorEnterCallback onMain window cb = onMain $ GLFW.setCursorEnterCallback window cb
setMouseButtonCallback :: EffectMain -> GLFW.Window -> Maybe GLFW.MouseButtonCallback -> IO ()
setMouseButtonCallback onMain window cb = onMain $ GLFW.setMouseButtonCallback window cb
getMouseButton :: OnMain GLFW.MouseButtonState -> GLFW.Window -> GLFW.MouseButton -> IO GLFW.MouseButtonState
getMouseButton onMain window button = onMain $ GLFW.getMouseButton window button
setStickyMouseButtonsInputMode :: EffectMain -> GLFW.Window -> GLFW.StickyMouseButtonsInputMode -> IO ()
setStickyMouseButtonsInputMode onMain window mode = onMain $ GLFW.setStickyMouseButtonsInputMode window mode
getStickyMouseButtonsInputMode :: OnMain GLFW.StickyMouseButtonsInputMode -> GLFW.Window -> IO GLFW.StickyMouseButtonsInputMode
getStickyMouseButtonsInputMode onMain window = onMain $ GLFW.getStickyMouseButtonsInputMode window
setScrollCallback :: EffectMain -> GLFW.Window -> Maybe GLFW.ScrollCallback -> IO ()
setScrollCallback onMain window cb = onMain $ GLFW.setScrollCallback window cb
getClipboardString :: OnMain (Maybe String) -> GLFW.Window -> IO (Maybe String)
getClipboardString onMain window = onMain $ GLFW.getClipboardString window
setClipboardString :: EffectMain -> GLFW.Window -> String -> IO ()
setClipboardString onMain window s = onMain $ GLFW.setClipboardString window s
setDropCallback :: EffectMain -> GLFW.Window -> Maybe GLFW.DropCallback -> IO ()
setDropCallback onMain window cb = onMain $ GLFW.setDropCallback window cb
getWindowSize :: OnMain (Int, Int) -> GLFW.Window -> IO (Int, Int )
getWindowSize onMain window = onMain $ GLFW.getWindowSize window