summaryrefslogtreecommitdiff
path: root/axis.hs
diff options
context:
space:
mode:
authorAndrew Cady <d@jerkface.net>2014-01-15 13:29:19 -0500
committerAndrew Cady <d@jerkface.net>2014-01-15 13:29:19 -0500
commit51922913bc0c32e5cacc3dd7a6c9e066cf3327ad (patch)
tree79065553ebf2545a4c8d0d166ceb5b57504e8c5e /axis.hs
parentd81a2d23d58e8cd9178ad21f802730d2fce31e40 (diff)
add fullscreen SDL graphics (empty black window)
Diffstat (limited to 'axis.hs')
-rw-r--r--axis.hs54
1 files changed, 41 insertions, 13 deletions
diff --git a/axis.hs b/axis.hs
index 7513163..64217ea 100644
--- a/axis.hs
+++ b/axis.hs
@@ -1,5 +1,6 @@
1{-# LANGUAGE StandaloneDeriving #-}
1import FRP.Netwire hiding (when) 2import FRP.Netwire hiding (when)
2import Prelude hiding ((.), id) 3import Prelude hiding ((.), id, null, filter)
3import Data.Time.Clock 4import Data.Time.Clock
4import Control.Wire hiding (when) 5import Control.Wire hiding (when)
5import Control.Wire.Session 6import Control.Wire.Session
@@ -21,17 +22,44 @@ netwireIsCool =
21 holdFor 0.5 . periodic 1 . pure "Hoo..." <|> 22 holdFor 0.5 . periodic 1 . pure "Hoo..." <|>
22 pure "...ray!" 23 pure "...ray!"
23 24
24main = SDL.withInit [SDL.InitVideo, SDL.InitTimer, SDL.InitJoystick] $ 25main =
25 withAlsaInit $ \h public private q publicAddr privateAddr -> do 26 withAlsaInit $ \h public private q publicAddr privateAddr -> do
27 cmdlineAlsaConnect h public -- fail early if bad command lines
28
29 SDL.withInit [SDL.InitVideo, SDL.InitTimer, SDL.InitJoystick] $ do
30 info <- SDL.getVideoInfo
31 let width = SDL.videoInfoWidth info
32 height = SDL.videoInfoHeight info
33--screen <- SDL.setVideoMode width height 32 [SDL.SWSurface, SDL.Fullscreen]
34 screen <- SDL.setVideoMode width height 32 [SDL.SWSurface]
26 putStrLn "Initialized." 35 putStrLn "Initialized."
27 loop clockSession_ netwireIsCool "" 36
28 where 37 let parseAlsa keysDown = parseAlsaEvents h keysDown (forwardNoteEvent h q publicAddr)
29 loop s w x = do 38 let loop midiKeysDown keysDown s w x = do
30 (ds, s') <- stepSession s 39 keysDown' <- parseSDLEvents keysDown
31 (ex, w') <- stepWire w ds (Right x) 40 midiKeysDown' <- parseAlsa midiKeysDown
32 let x' = either (const "") id ex 41 (ds, s') <- stepSession s
33 Control.Monad.when (x /= x' && x' /= "") $ putStrLn x' 42 (ex, w') <- stepWire w ds (Right x)
34 let framerate = 30 43 let x' = either (const "") id ex
35 let delay = 1000 `div` framerate - 1000 * (floor $ dtime ds) 44 Control.Monad.when (x /= x' && x' /= "") $ putStrLn x'
36 SDL.delay (delay) 45 let framerate = 30
37 loop s' w' x' 46 let delay = 1000 `div` framerate - 1000 * (floor $ dtime ds)
47 SDL.delay (delay)
48 Control.Monad.when (not $ keyDown SDL.SDLK_ESCAPE keysDown) $
49 loop midiKeysDown' keysDown' s' w' x'
50
51 loop Set.empty Set.empty clockSession_ netwireIsCool ""
52
53parseSDLEvents :: Set.Set SDL.Keysym -> IO (Set.Set SDL.Keysym)
54parseSDLEvents keysDown = do
55 event <- SDL.pollEvent
56 case event of
57 SDL.NoEvent -> return keysDown
58 SDL.KeyDown k -> parseSDLEvents (Set.insert k keysDown)
59 SDL.KeyUp k -> parseSDLEvents (Set.delete k keysDown)
60 _ -> parseSDLEvents keysDown
61
62keyDown :: SDL.SDLKey -> Set.Set SDL.Keysym -> Bool
63keyDown k = not . Set.null . Set.filter ((== k) . SDL.symKey)
64
65deriving instance Ord SDL.Keysym