Git Product home page Git Product logo

Comments (15)

Ashe avatar Ashe commented on August 15, 2024 3

Everything works as expected! Thanks for your hard work!

from reflex-sdl2.

schell avatar schell commented on August 15, 2024

Very interesting! Can you paste a minimal example so I can reproduce this locally?

from reflex-sdl2.

Ashe avatar Ashe commented on August 15, 2024

Here you go. Sorry if this isn't the most minimal it could be, but I used what I already had and just stripped parts out and put it all into one file.

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}

module Main where

import System.Exit (exitSuccess)

import Control.Monad
import Control.Monad.Fix

import SDL.Vect
import SDL (($=))
import qualified SDL

import Reflex
import Reflex.SDL2

import Foreign.C.Types

-- Entry point for the game
main :: IO ()
main = do

  -- Initialise SDL
  SDL.initialize [SDL.InitVideo, SDL.InitAudio, SDL.InitTimer, SDL.InitEvents]

  -- Create a window with the correct screensize and make it appear
  window <- SDL.createWindow "Bug" SDL.defaultWindow 

  -- Create a renderer for the window for rendering textures
  renderer <-
    SDL.createRenderer
      window
      (-1)
      SDL.RendererConfig
        { SDL.rendererType = SDL.AcceleratedRenderer
        , SDL.rendererTargetTexture = False
        }

  -- Create the initial state and put the player in
  let setup = initialSetup window renderer

  -- Set the window size
  SDL.windowSize window $= uncurry V2 (screenRes (options setup))

  -- Show the window
  SDL.showWindow window

  -- Begin the main game loop
  beginGame setup

-- The main game loop
game :: (ReflexSDL2 r t m, MonadDynamicWriter t [Layer m] m) => GameSetup -> m () 
game setup = do

  -- When the network is finished setting up
  gameReady <- getPostBuild

  -- Count when delta fires and compare at different times to calculate fps
  deltaCount <- count never

  -- Tick every quarterSecond
  secondCount <- getRecurringTimerEventWithEventCode 0 1000

  -- Quit on a quit event
  evQuit <- getQuitEvent
  performEvent_ $ ffor evQuit $ \() -> liftIO $ do
    SDL.quit
    SDL.destroyRenderer $ renderer setup
    SDL.destroyWindow $ window setup
    exitSuccess

-- Start the game loop properly
beginGame :: GameSetup -> IO ()
beginGame gs =
  host () $ do
    (_, dynLayers) <- runDynamicWriterT $ game gs
    performEvent_ $ ffor (updated dynLayers) $ \layers -> do
      rendererDrawColor r $= V4 0 0 0 255
      clear r
      sequence_ layers
      present r
  where w = window gs
        r = renderer gs

-- A type representing one layer in the game
type Layer m = Performable m ()

-- Hands the current state of the game to various functions
data GameSetup = 
  GameSetup
  { options     :: Options
  , window      :: SDL.Window
  , renderer    :: SDL.Renderer
  }

-- We will need this later so just making a newtype for now
newtype Options = Options{screenRes   :: (CInt, CInt)}

-- Create a GameSetup with some starting data easily
initialSetup :: SDL.Window -> SDL.Renderer -> GameSetup
initialSetup = GameSetup initialOptions

-- Create a set of Options with default values
initialOptions :: Options
initialOptions =
  Options
    { screenRes = (640, 480)
    }

The part that causes the behaviour is secondCount <- getRecurringTimerEventWithEventCode 0 1000, even when nothing is using the result of this line it still causes the error, so simply subscribing to this event causes the error.

One thing to note - when I open the program via a terminal, there's only a chance it manages to paste the line into the terminal, I believe this is when I close the game just as the tick time is coming up and so it executes as SDL closes. In a terminal, things stop completely, however when programming with Intero inside of neovim it continues to post messages so maybe try ghci.

It's not a massive problem, but I'm worried whether this means there's something not being freed or there's something wrong in the background that could cause problems for people down the road, hence why I wanted to flag it up. It's also annoying that I need to restart intero / the ghci in order to get a clean terminal without messages being posted.

Thanks!

from reflex-sdl2.

schell avatar schell commented on August 15, 2024

Your help is very much appreciated :). This is great.

from reflex-sdl2.

schell avatar schell commented on August 15, 2024

When using Intero are you quitting the app by introducing a quit event (by closing the window or selecting quit, ctrl-q, etc) or are you letting Intero do this for you (through recompiling or something similar)?

from reflex-sdl2.

Ashe avatar Ashe commented on August 15, 2024

I'm doing it via quitting the window as usual, and I know that it is using the quit event as it took me a while to understand why I wasn't able to close the window properly, and then I remembered how I'd do it in C++ haha. I hope this answer means that this issue is applicable to everyone and not just me.

from reflex-sdl2.

schell avatar schell commented on August 15, 2024

I’m about to merge the TriggerEvent pr - if you can check it out and try replacing those timers with delay then we’ll see if that fixes it.

from reflex-sdl2.

Ashe avatar Ashe commented on August 15, 2024

Thank you! I'll reply if it fixes it or not! But I'm using your work from stackage, will it be uploaded to there etc?

from reflex-sdl2.

schell avatar schell commented on August 15, 2024

Eventually yes, for now you’ll have to reference this commit in your stack.yaml - are you familiar with that?

from reflex-sdl2.

Ashe avatar Ashe commented on August 15, 2024

I am, yes. Thank you for your hard work! It does work, but I am still getting 'Video Substystem has not been initialised'. This time though, it happens even though getRecurringEventWithEventCode is commented out, and now delay is the culprit. Hopefully this gives you a little bit of insight as to what the problem is if you can find similarities in how they are implemented?

Thanks for everything! :)

from reflex-sdl2.

schell avatar schell commented on August 15, 2024

The last thing I'd like to try before I close this is to install a signal catcher to catch an external kill signal and clean up the trigger event thread. It could simply be a race condition that is solved by making sure reflex's network should stop before SDL stops.

from reflex-sdl2.

schell avatar schell commented on August 15, 2024

Oh! @Crysikrend also try this - in the quit section of game re-arrange the order of shutdown calls so SDL.quit is last:

  performEvent_ $ ffor evQuit $ \() -> liftIO $ do
    SDL.destroyRenderer $ renderer setup
    SDL.destroyWindow $ window setup
    SDL.quit
    exitSuccess

It looks like you can call quit after you've called each subsystem's shutdown, but SDL's docs don't say anything about calling a subsystem's shutdown after quit. Let me know if that solves it.

from reflex-sdl2.

Ashe avatar Ashe commented on August 15, 2024

@schell , unfortunately this does not work. I did think this would fix things, however the error now talks about the surface not having a colorkey. The error displayed changes depending on the order I close things, but thank you for reminding me to re-assess the order at which I close my game down once things have been fixed!

from reflex-sdl2.

schell avatar schell commented on August 15, 2024

Ok - I've done some other work that was much needed. Try out the new graceful shutdown example and see if that doesn't fix your problem. If it still doesn't work, I would start investigating Intero and ghci.

The completed work enables you to exit out of the reflex-sdl2 network with the following:

  evQuit <- getQuitEvent
  performEvent_ $ liftIO (putStrLn "bye!") <$ evQuit
  shutdownOn =<< delay 0 evQuit

The delay 0 evQuit above simply allows the putStrLn "bye!" to run before shutdown. shutdownOn will exit the main reflex-sdl2 loop (and other event processing loops) when the given Event fires. Then you can run your tear down after host returns, like so:

  -- Host the network with an example of how to embed your own effects.
  -- In this case it's a simple 'Renderer' reader.
  host $ runReaderT app r
  destroyRenderer r
  destroyWindow window
  quit

Let me know if that helps @Crysikrend :)

from reflex-sdl2.

Ashe avatar Ashe commented on August 15, 2024

Sorry for being so slow to reply, had a lot going on @schell

While this may work, I'm getting an error on build that I cannot do anything about - it's regarding the problem mentioned in issue #14 . Once this has been cleaned up I'll test again :)

from reflex-sdl2.

Related Issues (15)

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.