blob: 37b187f53a485c823e91caf64660e49675493bf9 (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
|
{-# LANGUAGE StandaloneDeriving #-}
import FRP.Netwire hiding (when)
import Prelude hiding ((.), id, null, filter)
import Data.Time.Clock
import Control.Wire hiding (when)
import Control.Wire.Session
import Control.Monad
import qualified Graphics.UI.SDL as SDL
import AlsaSeq
import qualified Data.Set as Set
import qualified Graphics.UI.SDL.TTF as SDL.TTF
netwireIsCool :: (Monad m) => Wire (Timed NominalDiffTime ()) () m a String
netwireIsCool =
for 2.5 . pure "Once upon a time..." -->
for 3 . pure "... games were completely imperative..." -->
for 2 . pure "... but then..." -->
for 10 . (pure "Netwire 5! " <> anim) -->
netwireIsCool
where
anim =
holdFor 0.5 . periodic 1 . pure "Hoo..." <|>
pure "...ray!"
main =
withAlsaInit $ \h public private q publicAddr privateAddr -> do
cmdlineAlsaConnect h public -- fail early if bad command lines
SDL.withInit [SDL.InitVideo, SDL.InitTimer, SDL.InitJoystick] $ do
info <- SDL.getVideoInfo
let width = SDL.videoInfoWidth info
height = SDL.videoInfoHeight info
--screen <- SDL.setVideoMode width height 32 [SDL.SWSurface, SDL.Fullscreen]
screen <- SDL.setVideoMode width height 32 [SDL.SWSurface]
_ <- SDL.TTF.init
font <- SDL.TTF.openFont "LiberationMono-Bold.ttf" 30
videoSurface <- SDL.getVideoSurface
videoClipRect <- SDL.getClipRect videoSurface
putStrLn "Initialized."
let parseAlsa keysDown = parseAlsaEvents h keysDown (forwardNoteEvent h q publicAddr)
let loop midiKeysDown keysDown s w x = do
keysDown' <- parseSDLEvents keysDown
midiKeysDown' <- parseAlsa midiKeysDown
(ds, s') <- stepSession s
(ex, w') <- stepWire w ds (Right x)
let x' = either (const "") id ex
Control.Monad.when (x /= x' && x' /= "") $ do
putStrLn x'
fontSurface <- SDL.TTF.renderUTF8Blended font x' (SDL.Color 0 255 0)
fontClipRect <- SDL.getClipRect fontSurface
-- _ <- SDL.fillRect videoSurface (Just fontClipRect) (SDL.Pixel 0)
_ <- SDL.fillRect videoSurface (Just videoClipRect) (SDL.Pixel 0)
_ <- SDL.blitSurface fontSurface (Just fontClipRect) videoSurface (Just fontClipRect)
-- _ <- SDL.updateRect videoSurface fontClipRect
_ <- SDL.updateRect videoSurface videoClipRect
return ()
let framerate = 30
let delay = 1000 `div` framerate - 1000 * (floor $ dtime ds)
SDL.delay (delay)
Control.Monad.when (not $ keyDown SDL.SDLK_ESCAPE keysDown) $
loop midiKeysDown' keysDown' s' w' x'
loop Set.empty Set.empty clockSession_ netwireIsCool ""
parseSDLEvents :: Set.Set SDL.Keysym -> IO (Set.Set SDL.Keysym)
parseSDLEvents keysDown = do
event <- SDL.pollEvent
case event of
SDL.NoEvent -> return keysDown
SDL.KeyDown k -> parseSDLEvents (Set.insert k keysDown)
SDL.KeyUp k -> parseSDLEvents (Set.delete k keysDown)
_ -> parseSDLEvents keysDown
keyDown :: SDL.SDLKey -> Set.Set SDL.Keysym -> Bool
keyDown k = not . Set.null . Set.filter ((== k) . SDL.symKey)
deriving instance Ord SDL.Keysym
|