]> andersk Git - scripts-static-cat.git/blame - StaticCat.hs
Ignore unparsable byte ranges.
[scripts-static-cat.git] / StaticCat.hs
CommitLineData
59962b4a
AK
1{-# LANGUAGE DeriveDataTypeable, ViewPatterns #-}
2{-# OPTIONS_GHC -O2 -Wall #-}
3
51cce206 4import Prelude hiding (catch)
59962b4a 5import Control.Applicative
59962b4a 6import Control.Monad
51cce206 7import Control.Monad.CatchIO
59962b4a 8import qualified Data.ByteString.Lazy as B
59cbcd42 9import Data.Char
59962b4a 10import Data.Dynamic
88f471e3 11import Data.Int
59962b4a
AK
12import qualified Data.Map as M
13import Data.Time.Clock.POSIX
14import Data.Time.Format
15import Network.CGI
16import Numeric
17import System.FilePath
18import System.IO
51cce206 19import System.IO.Error (isDoesNotExistError, isPermissionError)
88f471e3 20import System.IO.Unsafe
59962b4a
AK
21import System.Locale
22import System.Posix
23import System.Posix.Handle
24
25encodings :: M.Map String String
26encodings = M.fromList [
59cbcd42 27 (".bz2", "bzip2"),
59962b4a 28 (".gz", "gzip"),
59cbcd42 29 (".z", "compress")
59962b4a
AK
30 ]
31
32types :: M.Map String String
33types = M.fromList [
59cbcd42
AK
34 (".avi", "video/x-msvideo"),
35 (".css", "text/css"),
36 (".doc", "application/msword"),
37 (".gif", "image/gif"),
38 (".htm", "text/html"),
39 (".html", "text/html"),
40 (".ico", "image/vnd.microsoft.icon"),
41 (".il", "application/octet-stream"),
42 (".jar", "application/java-archive"),
43 (".jpeg", "image/jpeg"),
44 (".jpg", "image/jpeg"),
45 (".js", "application/x-javascript"),
46 (".mid", "audio/midi"),
47 (".midi", "audio/midi"),
48 (".mov", "video/quicktime"),
49 (".mp3", "audio/mpeg"),
50 (".mpeg", "video/mpeg"),
51 (".mpg", "video/mpeg"),
52 (".pdf", "application/pdf"),
53 (".png", "image/png"),
54 (".ppt", "application/vnd.ms-powerpoint"),
55 (".ps", "application/postscript"),
56 (".svg", "image/svg+xml"),
57 (".swf", "application/x-shockwave-flash"),
58 (".tar", "application/x-tar"),
59 (".tgz", "application/x-gzip"),
60 (".tif", "image/tiff"),
61 (".tiff", "image/tiff"),
62 (".wav", "audio/x-wav"),
63 (".wmv", "video/x-ms-wmv"),
64 (".xaml", "application/xaml+xml"),
65 (".xap", "application/x-silverlight-app"),
66 (".xhtml", "application/xhtml+xml"),
67 (".xls", "application/vnd.ms-excel"),
68 (".xml", "text/xml"),
69 (".xsl", "text/xml"),
70 (".zip", "application/zip")
59962b4a
AK
71 ]
72
59962b4a
AK
73data MyError = NotModified | Forbidden | NotFound | BadMethod | BadRange
74 deriving (Show, Typeable)
75
76instance Exception MyError
77
78outputMyError :: MyError -> CGI CGIResult
79outputMyError NotModified = setStatus 304 "Not Modified" >> outputNothing
80outputMyError Forbidden = outputError 403 "Forbidden" []
81outputMyError NotFound = outputError 404 "Not Found" []
82outputMyError BadMethod = outputError 405 "Method Not Allowed" []
83outputMyError BadRange = outputError 416 "Requested Range Not Satisfiable" []
84
85checkExtension :: FilePath -> CGI ()
86checkExtension file = do
87 let (base, ext) = splitExtension file
59cbcd42 88 ext' <- case M.lookup (map toLower ext) encodings of
59962b4a
AK
89 Nothing -> return ext
90 Just e -> do
91 setHeader "Content-Encoding" e
92 return $ takeExtension base
93
59cbcd42 94 case M.lookup (map toLower ext') types of
51cce206 95 Nothing -> throw Forbidden
59962b4a
AK
96 Just t -> setHeader "Content-Type" t
97
98checkMethod :: CGI CGIResult -> CGI CGIResult
99checkMethod rOutput = do
100 m <- requestMethod
101 case m of
102 "HEAD" -> rOutput >> outputNothing
103 "GET" -> rOutput
104 "POST" -> rOutput
51cce206 105 _ -> throw BadMethod
59962b4a
AK
106
107httpDate :: String
108httpDate = "%a, %d %b %Y %H:%M:%S %Z"
109formatHTTPDate :: EpochTime -> String
110formatHTTPDate = formatTime defaultTimeLocale httpDate .
111 posixSecondsToUTCTime . realToFrac
112parseHTTPDate :: String -> Maybe EpochTime
113parseHTTPDate = (fromInteger . floor . utcTimeToPOSIXSeconds <$>) .
114 parseTime defaultTimeLocale httpDate
115
116checkModified :: EpochTime -> CGI ()
117checkModified mTime = do
118 setHeader "Last-Modified" $ formatHTTPDate mTime
119 (requestHeader "If-Modified-Since" >>=) $ maybe (return ()) $ \ims ->
51cce206 120 when (parseHTTPDate ims >= Just mTime) $ throw NotModified
59962b4a
AK
121
122checkIfRange :: EpochTime -> CGI (Maybe ())
123checkIfRange mTime = do
124 (requestHeader "If-Range" >>=) $ maybe (return $ Just ()) $ \ir ->
125 return $ if parseHTTPDate ir == Just mTime then Just () else Nothing
126
127parseRange :: String -> FileOffset -> Maybe (FileOffset, FileOffset)
30782664
AK
128parseRange (splitAt 6 -> ("bytes=", '-':(readDec -> [(len, "")]))) size =
129 Just (max 0 (size - len), size - 1)
59962b4a
AK
130parseRange (splitAt 6 -> ("bytes=", readDec -> [(a, "-")])) size =
131 Just (a, size - 1)
374d09ff
AK
132parseRange (splitAt 6 -> ("bytes=", readDec -> [(a, '-':(readDec -> [(b, "")]))])) size =
133 Just (a, min (size - 1) b)
59962b4a
AK
134parseRange _ _ = Nothing
135
136checkRange :: EpochTime -> FileOffset -> CGI (Maybe (FileOffset, FileOffset))
137checkRange mTime size = do
138 setHeader "Accept-Ranges" "bytes"
139 (requestHeader "Range" >>=) $ maybe (return Nothing) $ \range -> do
140 (checkIfRange mTime >>=) $ maybe (return Nothing) $ \() -> do
141 case parseRange range size of
142 Just (a, b) | a <= b -> return $ Just (a, b)
9b3cd5c2
AK
143 Just _ -> throw BadRange
144 Nothing -> return Nothing
59962b4a 145
1cb5cdb0
AK
146outputAll :: Handle -> FileOffset -> CGI CGIResult
147outputAll h size = do
148 setHeader "Content-Length" $ show size
149 outputFPS =<< liftIO (B.hGetContents h)
150
88f471e3
AK
151-- | Lazily read a given number of bytes from the handle into a
152-- 'ByteString', then close the handle.
153hGetClose :: Handle -> Int64 -> IO B.ByteString
154hGetClose h len = do
155 contents <- B.hGetContents h
156 end <- unsafeInterleaveIO (hClose h >> return B.empty)
157 return (B.append (B.take len contents) end)
158
1cb5cdb0
AK
159outputRange :: Handle -> FileOffset -> Maybe (FileOffset, FileOffset) -> CGI CGIResult
160outputRange h size Nothing = outputAll h size
161outputRange h size (Just (a, b)) = do
162 let len = b - a + 1
163
164 setStatus 206 "Partial Content"
165 setHeader "Content-Range" $
166 "bytes " ++ show a ++ "-" ++ show b ++ "/" ++ show size
167 setHeader "Content-Length" $ show len
168 liftIO $ hSeek h AbsoluteSeek (fromIntegral a)
88f471e3 169 outputFPS =<< liftIO (hGetClose h (fromIntegral len))
1cb5cdb0 170
59962b4a 171serveFile :: FilePath -> CGI CGIResult
51cce206 172serveFile file = (`catch` outputMyError) $ do
59962b4a
AK
173 checkExtension file
174
175 checkMethod $ do
176
cee07ba6 177 let handleOpenError e =
51cce206
AK
178 if isDoesNotExistError e then throw NotFound
179 else if isPermissionError e then throw Forbidden
180 else throw e
181 h <- liftIO (openBinaryFile file ReadMode) `catch` handleOpenError
182 (`onException` liftIO (hClose h)) $ do
59962b4a
AK
183
184 status <- liftIO $ hGetStatus h
185 let mTime = modificationTime status
186 size = fileSize status
187 checkModified mTime
188
1cb5cdb0
AK
189 range <- checkRange mTime size
190 outputRange h size range
59962b4a
AK
191
192main :: IO ()
193main = runCGI $ handleErrors $ serveFile =<< pathTranslated
This page took 0.069166 seconds and 5 git commands to generate.