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