]> andersk Git - scripts-static-cat.git/blame - StaticCat.hs
static-cat: Add all MS Office (including OOXML) and ODF types
[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"),
6d268c6b
GT
37 (".docm", "application/vnd.ms-word.document.macroEnabled.12"),
38 (".docx", "application/vnd.openxmlformats-officedocument.wordprocessingml.document"),
39 (".dot", "application/msword"),
40 (".dotm", "application/vnd.ms-word.template.macroEnabled.12"),
41 (".dotx", "application/vnd.openxmlformats-officedocument.wordprocessingml.template"),
59cbcd42
AK
42 (".gif", "image/gif"),
43 (".htm", "text/html"),
44 (".html", "text/html"),
45 (".ico", "image/vnd.microsoft.icon"),
46 (".il", "application/octet-stream"),
47 (".jar", "application/java-archive"),
48 (".jpeg", "image/jpeg"),
49 (".jpg", "image/jpeg"),
50 (".js", "application/x-javascript"),
51 (".mid", "audio/midi"),
52 (".midi", "audio/midi"),
53 (".mov", "video/quicktime"),
54 (".mp3", "audio/mpeg"),
55 (".mpeg", "video/mpeg"),
56 (".mpg", "video/mpeg"),
6d268c6b
GT
57 (".odb", "application/vnd.oasis.opendocument.database"),
58 (".odc", "application/vnd.oasis.opendocument.chart"),
59 (".odf", "application/vnd.oasis.opendocument.formula"),
60 (".odg", "application/vnd.oasis.opendocument.graphics"),
61 (".odi", "application/vnd.oasis.opendocument.image"),
62 (".odm", "application/vnd.oasis.opendocument.text-master"),
63 (".odp", "application/vnd.oasis.opendocument.presentation"),
64 (".ods", "application/vnd.oasis.opendocument.spreadsheet"),
65 (".odt", "application/vnd.oasis.opendocument.text"),
3158b77a 66 (".otf", "application/octet-stream"),
6d268c6b
GT
67 (".otg", "application/vnd.oasis.opendocument.graphics-template"),
68 (".oth", "application/vnd.oasis.opendocument.text-web"),
69 (".otp", "application/vnd.oasis.opendocument.presentation-template"),
70 (".ots", "application/vnd.oasis.opendocument.spreadsheet-template"),
71 (".ott", "application/vnd.oasis.opendocument.text-template"),
59cbcd42
AK
72 (".pdf", "application/pdf"),
73 (".png", "image/png"),
6d268c6b
GT
74 (".pot", "application/vnd.ms-powerpoint"),
75 (".potm", "application/vnd.ms-powerpoint.template.macroEnabled.12"),
76 (".potx", "application/vnd.openxmlformats-officedocument.presentationml.template"),
77 (".ppa", "application/vnd.ms-powerpoint"),
78 (".ppam", "application/vnd.ms-powerpoint.addin.macroEnabled.12"),
79 (".pps", "application/vnd.ms-powerpoint"),
80 (".ppsm", "application/vnd.ms-powerpoint.slideshow.macroEnabled.12"),
81 (".ppsx", "application/vnd.openxmlformats-officedocument.presentationml.slideshow"),
59cbcd42 82 (".ppt", "application/vnd.ms-powerpoint"),
6d268c6b
GT
83 (".pptm", "application/vnd.ms-powerpoint.presentation.macroEnabled.12"),
84 (".pptx", "application/vnd.openxmlformats-officedocument.presentationml.presentation"),
59cbcd42
AK
85 (".ps", "application/postscript"),
86 (".svg", "image/svg+xml"),
87 (".swf", "application/x-shockwave-flash"),
88 (".tar", "application/x-tar"),
89 (".tgz", "application/x-gzip"),
90 (".tif", "image/tiff"),
91 (".tiff", "image/tiff"),
3158b77a 92 (".ttf", "application/octet-stream"),
59cbcd42
AK
93 (".wav", "audio/x-wav"),
94 (".wmv", "video/x-ms-wmv"),
95 (".xaml", "application/xaml+xml"),
96 (".xap", "application/x-silverlight-app"),
97 (".xhtml", "application/xhtml+xml"),
6d268c6b
GT
98 (".xla", "application/vnd.ms-excel"),
99 (".xlam", "application/vnd.ms-excel.addin.macroEnabled.12"),
59cbcd42 100 (".xls", "application/vnd.ms-excel"),
6d268c6b
GT
101 (".xlsb", "application/vnd.ms-excel.sheet.binary.macroEnabled.12"),
102 (".xlsm", "application/vnd.ms-excel.sheet.macroEnabled.12"),
103 (".xlsx", "application/vnd.openxmlformats-officedocument.spreadsheetml.sheet"),
104 (".xlt", "application/vnd.ms-excel"),
105 (".xltm", "application/vnd.ms-excel.template.macroEnabled.12"),
106 (".xltx", "application/vnd.openxmlformats-officedocument.spreadsheetml.template"),
59cbcd42
AK
107 (".xml", "text/xml"),
108 (".xsl", "text/xml"),
109 (".zip", "application/zip")
59962b4a
AK
110 ]
111
59962b4a
AK
112data MyError = NotModified | Forbidden | NotFound | BadMethod | BadRange
113 deriving (Show, Typeable)
114
115instance Exception MyError
116
117outputMyError :: MyError -> CGI CGIResult
118outputMyError NotModified = setStatus 304 "Not Modified" >> outputNothing
119outputMyError Forbidden = outputError 403 "Forbidden" []
120outputMyError NotFound = outputError 404 "Not Found" []
121outputMyError BadMethod = outputError 405 "Method Not Allowed" []
122outputMyError BadRange = outputError 416 "Requested Range Not Satisfiable" []
123
124checkExtension :: FilePath -> CGI ()
125checkExtension file = do
126 let (base, ext) = splitExtension file
59cbcd42 127 ext' <- case M.lookup (map toLower ext) encodings of
59962b4a
AK
128 Nothing -> return ext
129 Just e -> do
130 setHeader "Content-Encoding" e
131 return $ takeExtension base
132
59cbcd42 133 case M.lookup (map toLower ext') types of
51cce206 134 Nothing -> throw Forbidden
59962b4a
AK
135 Just t -> setHeader "Content-Type" t
136
137checkMethod :: CGI CGIResult -> CGI CGIResult
138checkMethod rOutput = do
139 m <- requestMethod
140 case m of
141 "HEAD" -> rOutput >> outputNothing
142 "GET" -> rOutput
143 "POST" -> rOutput
51cce206 144 _ -> throw BadMethod
59962b4a
AK
145
146httpDate :: String
147httpDate = "%a, %d %b %Y %H:%M:%S %Z"
148formatHTTPDate :: EpochTime -> String
149formatHTTPDate = formatTime defaultTimeLocale httpDate .
150 posixSecondsToUTCTime . realToFrac
151parseHTTPDate :: String -> Maybe EpochTime
152parseHTTPDate = (fromInteger . floor . utcTimeToPOSIXSeconds <$>) .
153 parseTime defaultTimeLocale httpDate
154
155checkModified :: EpochTime -> CGI ()
156checkModified mTime = do
157 setHeader "Last-Modified" $ formatHTTPDate mTime
158 (requestHeader "If-Modified-Since" >>=) $ maybe (return ()) $ \ims ->
51cce206 159 when (parseHTTPDate ims >= Just mTime) $ throw NotModified
59962b4a
AK
160
161checkIfRange :: EpochTime -> CGI (Maybe ())
162checkIfRange mTime = do
163 (requestHeader "If-Range" >>=) $ maybe (return $ Just ()) $ \ir ->
164 return $ if parseHTTPDate ir == Just mTime then Just () else Nothing
165
166parseRange :: String -> FileOffset -> Maybe (FileOffset, FileOffset)
30782664
AK
167parseRange (splitAt 6 -> ("bytes=", '-':(readDec -> [(len, "")]))) size =
168 Just (max 0 (size - len), size - 1)
59962b4a
AK
169parseRange (splitAt 6 -> ("bytes=", readDec -> [(a, "-")])) size =
170 Just (a, size - 1)
374d09ff
AK
171parseRange (splitAt 6 -> ("bytes=", readDec -> [(a, '-':(readDec -> [(b, "")]))])) size =
172 Just (a, min (size - 1) b)
59962b4a
AK
173parseRange _ _ = Nothing
174
175checkRange :: EpochTime -> FileOffset -> CGI (Maybe (FileOffset, FileOffset))
176checkRange mTime size = do
177 setHeader "Accept-Ranges" "bytes"
178 (requestHeader "Range" >>=) $ maybe (return Nothing) $ \range -> do
179 (checkIfRange mTime >>=) $ maybe (return Nothing) $ \() -> do
180 case parseRange range size of
181 Just (a, b) | a <= b -> return $ Just (a, b)
9b3cd5c2
AK
182 Just _ -> throw BadRange
183 Nothing -> return Nothing
59962b4a 184
1cb5cdb0
AK
185outputAll :: Handle -> FileOffset -> CGI CGIResult
186outputAll h size = do
187 setHeader "Content-Length" $ show size
188 outputFPS =<< liftIO (B.hGetContents h)
189
88f471e3
AK
190-- | Lazily read a given number of bytes from the handle into a
191-- 'ByteString', then close the handle.
192hGetClose :: Handle -> Int64 -> IO B.ByteString
193hGetClose h len = do
194 contents <- B.hGetContents h
195 end <- unsafeInterleaveIO (hClose h >> return B.empty)
196 return (B.append (B.take len contents) end)
197
1cb5cdb0
AK
198outputRange :: Handle -> FileOffset -> Maybe (FileOffset, FileOffset) -> CGI CGIResult
199outputRange h size Nothing = outputAll h size
200outputRange h size (Just (a, b)) = do
201 let len = b - a + 1
202
203 setStatus 206 "Partial Content"
204 setHeader "Content-Range" $
205 "bytes " ++ show a ++ "-" ++ show b ++ "/" ++ show size
206 setHeader "Content-Length" $ show len
207 liftIO $ hSeek h AbsoluteSeek (fromIntegral a)
88f471e3 208 outputFPS =<< liftIO (hGetClose h (fromIntegral len))
1cb5cdb0 209
59962b4a 210serveFile :: FilePath -> CGI CGIResult
51cce206 211serveFile file = (`catch` outputMyError) $ do
59962b4a
AK
212 checkExtension file
213
214 checkMethod $ do
215
cee07ba6 216 let handleOpenError e =
51cce206
AK
217 if isDoesNotExistError e then throw NotFound
218 else if isPermissionError e then throw Forbidden
219 else throw e
220 h <- liftIO (openBinaryFile file ReadMode) `catch` handleOpenError
221 (`onException` liftIO (hClose h)) $ do
59962b4a
AK
222
223 status <- liftIO $ hGetStatus h
224 let mTime = modificationTime status
225 size = fileSize status
226 checkModified mTime
227
1cb5cdb0
AK
228 range <- checkRange mTime size
229 outputRange h size range
59962b4a
AK
230
231main :: IO ()
232main = runCGI $ handleErrors $ serveFile =<< pathTranslated
This page took 0.117949 seconds and 5 git commands to generate.