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