-
Notifications
You must be signed in to change notification settings - Fork 0
/
RouteHandlers.hs
349 lines (316 loc) · 16.5 KB
/
RouteHandlers.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
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
module RouteHandlers where
import Data.Ord (comparing)
import Data.List (sortBy)
import Control.Monad (msum, liftM)
import qualified Data.ByteString.Char8 as C
import qualified Data.ByteString.UTF8 as B
import qualified Data.ByteString as BS
import qualified Data.Text as T
import qualified Data.Text.Encoding as E
import Data.Acid
import Data.Aeson
import LastFM.Request
import System.Process
import System.Exit ( ExitCode(..) )
import Control.Applicative (optional)
import Control.Monad.Trans (MonadIO, liftIO)
import Happstack.Server (port , Response , ServerPartT, ok , toResponse
,simpleHTTP, nullConf , seeOther , dir , notFound
,seeOther , asContentType, serveFile , ToMessage(..), look
,forbidden , queryString , decodeBody , defaultBodyPolicy
,BodyPolicy(..),method,lookCookieValue,unauthorized,badRequest )
import Happstack.Server.FileServe.BuildingBlocks (strictByteStringResponse, serveFileUsing)
import Happstack.Server.RqData (RqData, lookRead, getDataFn)
import qualified Happstack.Server.Cookie as Cookie
import Happstack.Server.Modified (filePathSendAllowRange)
import Happstack.Server.Internal.Types (Request(..),Method(..))
import Happstack.Server.Monads (askRq)
import Control.Concurrent (forkIO)
import Web.Routes.Boomerang
import Web.Routes ( PathInfo(..), RouteT , showURL , runRouteT
, Site(..) , setDefault, mkSitePI )
import Jobs
import Auth
import Routing
import HTTPClient
import Persistence
import JsonInstances
import Types
import qualified DataStructuresInternal as I
decodePolicy :: BodyPolicy
decodePolicy = (defaultBodyPolicy "/tmp/" 0 1000 1000)
site :: AcidState StereoidDb -> AcidState UserMap -> AcidState SessionMap -> Site Sitemap (ServerPartT IO Response)
site sdb users sessions = setDefault Home $ boomerangSite (runRouteT (route sdb users sessions)) sitemap
route :: AcidState StereoidDb -> AcidState UserMap -> AcidState SessionMap -> Sitemap -> RouteT Sitemap (ServerPartT IO) Response
route sdb users sessions url =
do decodeBody decodePolicy
rq <- askRq
let chk = checkToken sessions 15
-- let meth = rqMethod rq
case rqMethod rq of
GET -> case url of
(Stream songId) -> serveSong sdb songId
(AlbumInfo albumId) -> chk $ albumData sdb albumId
(ArtistInfo artistId) -> chk $ artistData sdb artistId
(ArtistAlbums artistId) -> chk $ artistAlbums sdb artistId
(Songs) -> chk $ songsAll sdb
(Artists) -> chk $ artistsAll sdb
(Albums) -> chk $ albumsAll sdb
(AlbumSongs albumId) -> chk $ albumSongs sdb albumId
(AlbumM3U albumId) -> chk $ albumSongsM3U sdb albumId
(AlbumArt albumId) -> chk $ serveArt sdb albumId
(AlbumArtThumb albumId) -> chk $ serveGenThumb sdb albumId
(Jobs) -> chk $ jobsAll sdb
(JobInfo jobId) -> chk $ jobData sdb jobId
(Catalogs) -> chk $ catalogsAll sdb
(CatalogInfo catalogId) -> chk $ catalogData sdb catalogId
PUT -> case url of
(Sessions) -> chk $ ok (toResponse "Session extended.")
(CatalogInfo catalogId) -> chk $ startJob sdb
POST -> case url of
(Sessions) -> authorize users sessions
(AlbumArt albumId) -> chk $ getArtFromUrl sdb albumId
(Users) -> chk $ addUser users
(Catalogs) -> chk $ catalogNew sdb
catalogNew :: AcidState StereoidDb -> RouteT Sitemap (ServerPartT IO) Response
catalogNew sdb = undefined
catalogsAll :: AcidState StereoidDb -> RouteT Sitemap (ServerPartT IO) Response
catalogsAll sdb = undefined
catalogData :: AcidState StereoidDb -> CatalogId -> RouteT Sitemap (ServerPartT IO) Response
catalogData sdb (CatalogId id) = undefined
startJob :: AcidState StereoidDb -> RouteT Sitemap (ServerPartT IO) Response
startJob sdb = do
id <- getFreeJobId sdb
liftIO $ forkIO $ addToStereoidDb id "/mnt/emusic" sdb
ok $ toResponse "Job started"
jobsAll :: AcidState StereoidDb -> RouteT Sitemap (ServerPartT IO) Response
jobsAll sdb = do
jobs <- getJobs sdb
ok $ toResponse $ toJSON jobs
jobData :: AcidState StereoidDb -> JobId -> RouteT Sitemap (ServerPartT IO) Response
jobData sdb (JobId id) = do
job <- getJob sdb id
case job of
Nothing -> notFound $ toResponse "What you are looking for has not been found."
Just x -> ok $ toResponse $ toJSON x
checkToken :: AcidState SessionMap -> Integer ->
RouteT Sitemap (ServerPartT IO) Response ->
RouteT Sitemap (ServerPartT IO) Response
checkToken sessions min f = do
token <- msum [lookCookieValue "token", look "token"]
user <- checkExtendSession sessions 15 token
case user of
Nothing -> unauthorized $ toResponse $ "Invalid token"
Just _ -> f
addUser :: AcidState UserMap -> RouteT Sitemap (ServerPartT IO) Response
addUser acid = do
user <- look "username"
pass <- look "password"
result <- (newUser acid user pass)
case result of
Right _ -> ok (toResponse $ "User " ++ user ++ " created.")
Left m -> forbidden (toResponse $ show m)
authorize :: AcidState UserMap -> AcidState SessionMap -> RouteT Sitemap (ServerPartT IO) Response
authorize users sessions = do
username <- look "username"
lt <- getDataFn $ look "logintoken"
case lt of
(Left _ ) -> do
hash <- look "auth"
salt <- look "timestamp"
auth <- (authUser users username hash salt)
if auth then do
token <- (newSession sessions 60 username)
rq <- getDataFn $ look "rememberme"
case rq of
(Left _) -> ok $ toResponse $ toJSON Session { sessionToken = token }
(Right _) -> do lT <- newRememberMe sessions username
ok $ toResponse $ toJSON Remember { rSessionToken = token, rRememberToken = lT }
else
forbidden $ toResponse $ "Invalid username/password"
(Right logintoken) -> do
rq <- checkRenewRememberMe sessions logintoken username
case rq of
Nothing -> forbidden $ toResponse $ "Invalid login token"
Just newtoken -> do
sess <- newSession sessions 60 username
ok $ toResponse $ toJSON Remember { rSessionToken = sess, rRememberToken = newtoken }
songAddUrl :: I.Song -> RouteT Sitemap (ServerPartT IO) Song
songAddUrl I.Song { I.songID = id
, I.songName = name
, I.songTrack = track
, I.songAlbumId = albumID
, I.songAlbumTitle = albumtitle
, I.songArtistName = artistname
, I.songDuration = time
} = do surl <- (showURL (Stream (SongId id) ))
aurl <- (showURL (AlbumArt (AlbumId albumID) ))
return Song { songID = id
, songName = name
, songTrack = track
, songUrl = surl
, songArtUrl = aurl
, songAlbumId = albumID
, songAlbumTitle = albumtitle
, songArtistName = artistname
, songDuration = time
}
albumAddUrl :: I.Album -> RouteT Sitemap (ServerPartT IO) Album
albumAddUrl I.Album { I.albumID = id
, I.albumTitle = title
, I.albumYear = year
, I.albumArtistID = artistid
, I.albumArtistName = artist
} = do aurl <- (showURL (AlbumArt (AlbumId id)))
turl <- (showURL (AlbumArtThumb (AlbumId id)))
surl <- (showURL (AlbumSongs (AlbumId id)))
murl <- (showURL (AlbumM3U (AlbumId id)))
return Album { albumID = id
, albumTitle = title
, albumArtistID = artistid
, albumArtistName = artist
, albumYear = year
, albumArtUrl = aurl
, albumArtThumbUrl = turl
, albumSongsUrl = surl
, albumM3UUrl = murl
}
albumSongs :: AcidState StereoidDb -> AlbumId -> RouteT Sitemap (ServerPartT IO) Response
albumSongs sdb (AlbumId id) = do
sgs <- getSongsByAlbumId sdb id
songs <- mapM songAddUrl sgs
ok $ toResponse $ toJSON $ sortBy (comparing songTrack) songs
albumSongsM3U :: AcidState StereoidDb -> AlbumId -> RouteT Sitemap (ServerPartT IO) Response
albumSongsM3U sdb (AlbumId id) = do
sgs <- getSongsByAlbumId sdb id
songs <- mapM songAddUrl sgs
case songs of
[] -> notFound $ toResponse "What you are looking for has not been found."
xs -> ok $ toResponse $ createM3u xs
albumData :: AcidState StereoidDb -> AlbumId -> RouteT Sitemap (ServerPartT IO) Response
albumData sdb (AlbumId albumid) = do
album <- getAlbum sdb albumid
case album of
Nothing -> notFound $ toResponse "What you are looking for has not been found."
Just al -> do alb <- albumAddUrl al
ok $ toResponse $ toJSON alb
getArtFromUrl :: AcidState StereoidDb -> AlbumId -> RouteT Sitemap (ServerPartT IO) Response
getArtFromUrl sdb (AlbumId artid) = do
qs <- getDataFn $ lookRead "url"
al <- getAlbum sdb artid
case al of
(Just album) -> do
image <- case qs of
(Left _) -> do
fmr <- liftIO $ getLastFmArtUrl (E.decodeUtf8 $ I.albumArtistName album) (E.decodeUtf8 $ I.albumTitle album)
case fmr of
Nothing -> return (Left "error")
Just url -> liftIO $ downloadFileWithMime url
(Right u) -> liftIO $ downloadFileWithMime u
case image of
Left _ -> notFound $ toResponse "What you are looking for has not been found."
Right (Just mime, resp) -> do liftIO $ BS.writeFile (afn artid) resp
addArt sdb artid mime (afn artid)
ok $ toResponse "Art added."
where afn x = ("art/" ++ (show x))
_ -> notFound $ toResponse "What you are looking for has not been found."
{-
getThumbFromUrl :: AcidState StereoidDb -> AlbumId -> RouteT Sitemap (ServerPartT IO) Response
getThumbFromUrl sdb (AlbumId artid) = do
url <- look "url"
image <- liftIO $ downloadFileWithMime url
case image of
Left x -> notFound $ toResponse "What you are looking for has not been found."
Right (Just mime, resp) -> do liftIO $ BS.writeFile (afn artid) resp
addThumb sdb artid mime (afn artid)
ok $ toResponse "Thumb added."
where afn x = ("thumb/" ++ (show x))
-}
serveArt :: AcidState StereoidDb -> AlbumId -> RouteT Sitemap (ServerPartT IO) Response
serveArt sdb (AlbumId artid) = do
dr <- getArt sdb artid
case dr of
Just (mime,art) -> serveFileUsing filePathSendAllowRange (asContentType $ B.toString mime) $ art
Nothing -> serveFile (asContentType "image/png") "media_album.png"
serveGenThumb :: AcidState StereoidDb -> AlbumId -> RouteT Sitemap (ServerPartT IO) Response
serveGenThumb sdb (AlbumId artid) = do
dr <- getThumb sdb artid
case dr of
Just (tmime,tart) -> serveFileUsing filePathSendAllowRange (asContentType $ B.toString tmime) $ tart
Nothing -> do
aa <- getArtData sdb artid
case aa of
Nothing -> serveFile (asContentType "image/png") "media_album.png"
Just (AlbumArtData amime file _ _) -> do
let tfn = ("thumb/" ++ (show artid))
result <- liftIO $ system $ "convert " ++ file ++ " -resize '200x200!>' " ++ tfn
case result of
ExitSuccess -> do
insertRowAlbumArtDb sdb artid (AlbumArtData amime file (Just amime) (Just tfn))
serveFileUsing filePathSendAllowRange (asContentType $ B.toString amime) $ tfn
ExitFailure _ -> serveFile (asContentType "image/png") "media_album.png"
serveThumb :: AcidState StereoidDb -> AlbumId -> RouteT Sitemap (ServerPartT IO) Response
serveThumb sdb (AlbumId artid) = do
dr <- getThumb sdb artid
case dr of
Just (mime,art) -> serveFileUsing filePathSendAllowRange (asContentType $ B.toString mime) $ art
Nothing -> serveFile (asContentType "image/png") "media_album.png"
serveSong :: AcidState StereoidDb -> SongId -> RouteT Sitemap (ServerPartT IO) Response
serveSong sdb SongId { unSongId = songid } = do
song <- getSongFile sdb songid
case song of
Nothing -> notFound $ toResponse "What you are looking for has not been found."
Just sf -> serveFileUsing filePathSendAllowRange (asContentType "audio/mpeg3") $ C.unpack sf
artistData :: AcidState StereoidDb -> ArtistId -> RouteT Sitemap (ServerPartT IO) Response
artistData sdb (ArtistId id) = do
artist <- getArtist sdb id
case artist of
Nothing -> notFound $ toResponse "What you are looking for has not been found."
Just ar -> ok $ toResponse $ toJSON ar
artistAlbums :: AcidState StereoidDb -> ArtistId -> RouteT Sitemap (ServerPartT IO) Response
artistAlbums sdb (ArtistId id) = do
albs <- getAlbumsByArtistId sdb id
albums <- mapM albumAddUrl albs
ok $ toResponse $ toJSON albums
artistsAll :: AcidState StereoidDb -> RouteT Sitemap (ServerPartT IO) Response
artistsAll sdb = do
artists <- getArtists sdb
ok $ toResponse $ toJSON artists
songsAll :: AcidState StereoidDb -> RouteT Sitemap (ServerPartT IO) Response
songsAll sdb = do
ol <- getOffsetLimit
filter <- getDataFn $ lookRead "title"
let fSongs = case filter of
(Left e) -> getSongs sdb ol
(Right r) -> filterSongTrie sdb (E.encodeUtf8 $ T.toUpper $ T.pack r)
sos <- fSongs
songs <- mapM songAddUrl sos
ok $ toResponse $ toJSON songs
albumsAll :: AcidState StereoidDb -> RouteT Sitemap (ServerPartT IO) Response
albumsAll sdb = do
ol <- getOffsetLimit
filter <- getDataFn $ lookRead "artist"
sort <- getDataFn $ lookRead "sort"
let getAlbs = case filter of
(Left e) -> case sort of
(Left e) -> getAlbums sdb ol
(Right "random") -> do
s <- getDataFn $ lookRead "seed"
case s of
(Left e) -> getAlbums sdb ol
(Right r) -> getAlbumsRandom sdb ol r
(Right r) -> filterArtistTrie sdb (E.encodeUtf8 $ T.toUpper $ T.pack r)
albs <- getAlbs
albums <- mapM albumAddUrl albs
ok $ toResponse $ toJSON albums
getOffsetLimit :: RouteT Sitemap (ServerPartT IO) (Int,Int)
getOffsetLimit = do
r <- getDataFn $ lookRead "offset"
s <- getDataFn $ lookRead "limit"
let offset = case r of
(Left e) -> 0
(Right i) -> i
let limit = case s of
(Left e) -> 50
(Right i) -> i
return (offset,limit)