-
Notifications
You must be signed in to change notification settings - Fork 7
/
GifStream.hs
180 lines (148 loc) · 5.27 KB
/
GifStream.hs
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
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
{-# LANGUAGE OverloadedStrings #-}
-- | Generate dynamic GIF streams and provide them on an HTTP server.
module GifStream (
-- Functions
server,
-- Types
RGB,
Frame,
FrameSignal,
Logic
)
where
import System.IO
import Network.Socket
import Network.Socket.ByteString (sendAll)
import Control.Monad
import Control.Concurrent
import Data.IORef
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8() -- for OverloadedStrings
type RGB = (Int,Int,Int) -- ^ Values in [0..3]
type Frame = [[RGB]]
type FrameSignal = MSignal Frame
type Logic = IO () -> IO Char -> (Frame -> IO ()) -> IO ()
-- | Run an HTTP server that delivers a continuing stream of a GIF to every
-- incoming connections. A logic function is called to generate the GIF
-- frames.
server :: PortNumber -> Int -> Logic -> IO ()
server port delay logic = withSocketsDo $ do
hSetBuffering stdin NoBuffering
sock <- socket AF_INET Stream 0
setSocketOption sock ReuseAddr 1
bind sock (SockAddrInet port 0)
listen sock 10 -- Allow 10 concurrent users
putStrLn $ "Listening on http://127.0.0.1:" ++ show port ++ "/"
wait <- getMetronome delay
getAction <- inputGetter
frameSignal <- newMSignal
forkIO $ loop delay frameSignal sock
logic wait getAction $ sendMSignal frameSignal
-- | Wait for incoming connections and start delivering a GIF to them
loop :: Int -> FrameSignal -> Socket -> IO ()
loop delay frameSignal sock = do
(conn, _) <- accept sock
forkIO $ body conn
loop delay frameSignal sock
where -- lower delay in GIF to force browser to actually show the gif we send
body c = do
f <- receiveMSignal frameSignal
sendAll c $ msg $ initialFrame (delay `div` 20000) f
nextFrame c
nextFrame c = do
f <- receiveMSignal frameSignal
sendAll c $ frame (delay `div` 20000) f
nextFrame c
msg content = B.intercalate "\r\n"
[ "HTTP/1.0 200 OK"
, "Server: gifstream/0.1"
, "Content-Type: image/gif"
, "Content-Transfer-Encoding: binary"
, ""
, content
]
-- | Get a function that waits for the specified time whenever it's called
getMetronome :: Int -> IO (IO ())
getMetronome delay = do
var <- newMVar ()
forkIO $ forever $ do
threadDelay delay
putMVar var ()
return $ takeMVar var
-- | Get a function that returns the last key pressed whenever it's called
inputGetter :: IO (IO Char)
inputGetter = do
inputRef <- newIORef 'd' -- Default input
forkIO $ forever $ do
c <- getChar
writeIORef inputRef c
return $ readIORef inputRef
-- | Create the initial frame of a GIF. Note that this frame determines the size of the GIF.
initialFrame :: Int -> Frame -> B.ByteString
initialFrame delay img = B.concat
[ "GIF89a"
, number w, number h, gctInfo, bgColor, aspect -- logical screen descriptor
, realCT, dummyCT -- color table
, "!\255\vNETSCAPE2.0\ETX\SOH\NUL\NUL\NUL" -- application extension
, frame delay img
]
where
w = length $ head img
h = length img
gctInfo = B.singleton 0xf6
bgColor = smallNumber 127
aspect = "\NUL"
realCT = B.concat $ map B.pack [[r,g,b] | r <- colors, g <- colors, b <- colors]
colors = [0,64,128,255]
dummyCT = B.concat $ replicate 64 $ B.pack [255,255,255]
-- | Create the next frame in a GIF
frame :: Int -> Frame -> B.ByteString
frame delay img = B.concat
[ "!\249\EOT\b", number delay, "\255", "\NUL" -- graphic control extension
, ",", yPos, xPos, number w, number h, localCT -- image descriptor
, lzwMinSize, imageData, "\NUL" -- image
]
where
w = length $ head img
h = length img
yPos = number 0
xPos = number 0
localCT = "\NUL"
lzwMinSize = B.singleton 0x07
imageData = B.concat $ map (B.concat . mapLine) img
mapLine x
| null ys = z
| otherwise = z ++ mapLine ys
where (y,ys) = splitAt 126 x
z = [ bytesToFollow, clear
, B.pack $ map (\(r,g,b) -> fromIntegral $ 16*r+4*g+b) y
]
bytesToFollow = smallNumber $ length y + 1
clear = B.singleton 0x80
-- | Close the GIF file
finalize :: B.ByteString
finalize = B.concat [bytesToFollow, stop, "\NUL", ";"]
where
bytesToFollow = smallNumber 1
stop = B.singleton 0x81
-- | Convert a number to one Byte
smallNumber :: Int -> B.ByteString
smallNumber x = B.singleton $ fromIntegral $ x `mod` 256
-- | Convert a number to two Bytes
number :: Int -> B.ByteString
number x = B.pack $ map fromIntegral [x `mod` 256, x `div` 256]
-- | A Module for broadcast signalling between threads.
-- By Joachim Breitner
-- | MSignal is an opaque data type
newtype MSignal a = MS (MVar a)
-- | Creates a new MSignal object. This can be used to send and receive signals, possibly containing some data. If you do not want to transmit data, use @'MSignal' ()@
newMSignal :: IO (MSignal a)
newMSignal = MS `liftM` newEmptyMVar
-- | Sends new data to all threads currently running 'receiveMSignal'
sendMSignal :: MSignal a -> a -> IO ()
sendMSignal (MS mv) v = do
forkIO $ takeMVar mv >> return () -- Cleanup afterwards
putMVar mv v
-- | Blocks until another threads sends data using 'sendMSignal'. It then returns the sent data.
receiveMSignal :: MSignal a -> IO a
receiveMSignal (MS mv) = readMVar mv