finishing cleanup

This commit is contained in:
nek0 2018-09-25 17:27:35 +02:00
parent 3935b7ddb9
commit f822b5cabb
4 changed files with 8 additions and 5 deletions

View File

@ -85,7 +85,7 @@ withAffection AffectionConfig{..} = do
(_, nState) <- runStateT ( A.runState $ do
liftIO $ logIO Debug "Starting Loop"
preLoop
whileM_ (not . A.quitEvent current <$> get)
whileM_ (not . A.quitEvent <$> get)
(do
-- get state
ad <- get

View File

@ -21,7 +21,8 @@ import Affection.Logging
-- | This typeclass defines the behaviour of a participant in the message system
class (Message (Mesg prt us), Show (Mesg prt us)) => Participant prt us where
type Mesg prt us :: * -- ^ Message datatype
-- | Message datatype
type Mesg prt us :: *
-- | Function to get the list of subscribers from the participant
partSubscribers

View File

@ -95,13 +95,13 @@ joystickAutoConnect _ = return Nothing
joystickAutoDisconnect
:: [SDL.Joystick] -- ^ List of Joystick descriptors
-> JoystickMessage -- ^ Any 'JoystickMessage' will do, but listens
-- specifically to 'MsgJoystickDevice' messages
-- specifically to 'MsgJoystickDevice' messages
-> Affection us [SDL.Joystick] -- ^ Returns altered list of Joystick descriptors
joystickAutoDisconnect js (MsgJoystickDevice _ which SDL.JoyDeviceRemoved) =
liftIO $ do
joyIds <- mapM SDL.getJoystickID js
logIO Verbose $ "These are the Joysticks connected: " ++ show joyIds
[d] <- filterM ((which ==) <$> SDL.getJoystickID) js
[d] <- filterM (\j -> fmap (== which) (SDL.getJoystickID j)) js
logIO Verbose $ "disconnected joysticks: " ++ show d
logIO Verbose $ "Disconnecting Joystick " ++ show which
SDL.closeJoystick d

View File

@ -12,7 +12,7 @@ import System.Clock
import Control.Monad.State
-- Prehandle SDL events in case any window events occur
-- | Prehandle SDL events
preHandleEvents :: [SDL.Event] -> Affection us [SDL.EventPayload]
preHandleEvents evs =
return $ map SDL.eventPayload evs
@ -40,9 +40,11 @@ delaySec dur = SDL.delay (fromIntegral $ dur * 1000)
getElapsedTime :: Affection us Double
getElapsedTime = gets elapsedTime
-- | Get delta time (time elapsed from last frame)
getDelta :: Affection us Double
getDelta = gets deltaTime
-- | Quit the engine loop
quit :: Affection us ()
quit = do
ad <- get