]> gitweb @ CieloNegro.org - Lucu.git/blob - Network/HTTP/Lucu/MIMEType/Guess.hs
Optimized as possible as I can.
[Lucu.git] / Network / HTTP / Lucu / MIMEType / Guess.hs
1 -- |MIME Type guesser which guesses by a file extension. This is a
2 -- poor man's way of guessing MIME Types. It is simple and fast.
3 --
4 -- In general you don't have to use this module directly.
5 module Network.HTTP.Lucu.MIMEType.Guess
6     ( ExtMap
7     , guessTypeByFileName
8
9     , parseExtMapFile
10     , serializeExtMap
11     )
12     where
13
14 import qualified Data.ByteString.Lazy.Char8 as B
15 import           Data.ByteString.Lazy.Char8 (ByteString)
16 import qualified Data.Map as M
17 import           Data.Map (Map)
18 import           Data.Maybe
19 import           Language.Haskell.Pretty
20 import           Language.Haskell.Syntax
21 import           Network.HTTP.Lucu.MIMEType
22 import           Network.HTTP.Lucu.Parser
23 import           Network.HTTP.Lucu.Parser.Http
24 import           Network.HTTP.Lucu.Utils
25 import           System.IO
26
27 -- |Map from extension to MIME Type.
28 type ExtMap = Map String MIMEType
29
30 -- |Guess the MIME Type of file.
31 guessTypeByFileName :: ExtMap -> FilePath -> Maybe MIMEType
32 guessTypeByFileName extMap fpath
33     = extMap `seq` fpath `seq`
34       let ext = last $ splitBy (== '.') fpath
35       in
36         M.lookup ext extMap >>= return
37
38 -- |Read an Apache mime.types and parse it.
39 parseExtMapFile :: FilePath -> IO ExtMap
40 parseExtMapFile fpath
41     = fpath `seq`
42       do file <- B.readFile fpath
43          case parse (allowEOF extMapP) file of
44            (Success xs, _) -> return $ compile xs
45            (_, input')     -> let near = B.unpack $ B.take 100 input'
46                               in 
47                                 fail ("Failed to parse: " ++ fpath ++ " (near: " ++ near ++ ")")
48
49
50 extMapP :: Parser [ (MIMEType, [String]) ]
51 extMapP = do xs <- many (comment <|> validLine <|> emptyLine)
52              eof
53              return $ catMaybes xs
54     where
55       spc = oneOf " \t"
56
57       comment = do many spc
58                    char '#'
59                    many $ satisfy (/= '\n')
60                    return Nothing
61
62       validLine = do many spc
63                      mime <- mimeTypeP
64                      many spc
65                      exts <- sepBy token (many spc)
66                      return $ Just (mime, exts)
67
68       emptyLine = oneOf " \t\n" >> return Nothing
69
70
71 compile :: [ (MIMEType, [String]) ] -> Map String MIMEType
72 compile = M.fromList . foldr (++) [] . map tr
73     where
74       tr :: (MIMEType, [String]) -> [ (String, MIMEType) ]
75       tr (mime, exts) = [ (ext, mime) | ext <- exts ]
76
77 -- |@'serializeExtMap' extMap moduleName variableName@ generates a
78 -- Haskell source code which contains the following things:
79 --
80 -- * A definition of module named @moduleName@.
81 --
82 -- * @variableName :: 'ExtMap'@ whose content is a serialization of
83 --   @extMap@.
84 --
85 -- The module "Network.HTTP.Lucu.MIMEType.DefaultExtensionMap" is
86 -- surely generated using this function.
87 serializeExtMap :: ExtMap -> String -> String -> String
88 serializeExtMap extMap moduleName variableName
89     = let hsModule = HsModule undefined modName (Just exports) imports decls
90           modName  = Module moduleName
91           exports  = [HsEVar (UnQual (HsIdent variableName))]
92           imports  = [ HsImportDecl undefined (Module "Network.HTTP.Lucu.MIMEType") False Nothing Nothing
93                      , HsImportDecl undefined (Module "Network.HTTP.Lucu.MIMEType.Guess") False Nothing Nothing
94                      , HsImportDecl undefined (Module "Data.Map") True (Just (Module "M")) Nothing
95                      , HsImportDecl undefined (Module "Data.Map") False Nothing (Just (False, [HsIAbs (HsIdent "Map")]))
96                      ]
97           decls    = [ HsTypeSig undefined [HsIdent variableName]
98                                      (HsQualType []
99                                       (HsTyCon (UnQual (HsIdent "ExtMap"))))
100                      , HsFunBind [HsMatch undefined (HsIdent variableName)
101                                   [] (HsUnGuardedRhs extMapExp) []]
102                      ]
103           extMapExp = HsApp (HsVar (Qual (Module "M") (HsIdent "fromList"))) (HsList records)
104           comment =    "{- !!! WARNING !!!\n"
105                     ++ "   This file is automatically generated.\n"
106                     ++ "   DO NOT EDIT BY HAND OR YOU WILL REGRET -}\n\n"
107       in
108         comment ++ prettyPrint hsModule ++ "\n"
109     where
110       records :: [HsExp]
111       records = map record $ M.assocs extMap
112
113       record :: (String, MIMEType) -> HsExp
114       record (ext, mime)
115           = HsTuple [HsLit (HsString ext), mimeToExp mime]
116                     
117       mimeToExp :: MIMEType -> HsExp
118       mimeToExp (MIMEType maj min params)
119           = foldl appendParam (HsInfixApp
120                                (HsLit (HsString maj))
121                                (HsQVarOp (UnQual (HsSymbol "</>")))
122                                (HsLit (HsString min))) params
123
124       appendParam :: HsExp -> (String, String) -> HsExp
125       appendParam x param
126           = HsInfixApp x (HsQVarOp (UnQual (HsSymbol "<:>"))) $ paramToExp param
127
128       paramToExp :: (String, String) -> HsExp
129       paramToExp (name, value)
130           = HsInfixApp
131             (HsLit (HsString name))
132             (HsQVarOp (UnQual (HsSymbol "<=>")))
133             (HsLit (HsString value))