]> gitweb @ CieloNegro.org - Lucu.git/blob - Network/HTTP/Lucu/MIMEType/Guess.hs
Reimplement MultipartForm
[Lucu.git] / Network / HTTP / Lucu / MIMEType / Guess.hs
1 {-# LANGUAGE
2     UnicodeSyntax
3   #-}
4 -- |Guessing MIME Types by file extensions. It's not always accurate
5 -- but simple and fast.
6 --
7 -- In general you don't have to use this module directly.
8 module Network.HTTP.Lucu.MIMEType.Guess
9     ( ExtMap
10     , guessTypeByFileName
11
12     , parseExtMapFile
13     , serializeExtMap
14     )
15     where
16 import Control.Applicative
17 import Control.Monad
18 import qualified Data.Ascii as A
19 import Data.Attoparsec.Char8 as P
20 import qualified Data.Attoparsec.Lazy as LP
21 import qualified Data.ByteString.Lazy.Char8 as B
22 import qualified Data.Map as M
23 import Data.Map (Map)
24 import Data.Maybe
25 import Data.Monoid.Unicode
26 import Data.Text (Text)
27 import qualified Data.Text as T
28 import Data.Text.Encoding
29 import Language.Haskell.Exts.Build
30 import Language.Haskell.Exts.Extension
31 import Language.Haskell.Exts.Pretty
32 import Language.Haskell.Exts.Syntax
33 import Network.HTTP.Lucu.MIMEType
34 import Prelude.Unicode
35 import System.FilePath
36
37 -- |A 'Map' from file extensions to 'MIMEType's.
38 type ExtMap = Map Text MIMEType
39
40 -- |Guess the MIME Type of a file.
41 guessTypeByFileName ∷ ExtMap → FilePath → Maybe MIMEType
42 guessTypeByFileName extMap fpath
43     = case takeExtension fpath of
44         []      → Nothing
45         (_:ext) → M.lookup (T.pack ext) extMap
46
47 -- |Read an Apache mime.types and parse it.
48 parseExtMapFile ∷ FilePath → IO ExtMap
49 parseExtMapFile fpath
50     = do file ← B.readFile fpath
51          case LP.parse extMapP file of
52            LP.Done _ xs
53                → case compile xs of
54                     Right m → return m
55                     Left  e → fail (concat [ "Duplicate extension \""
56                                            , show e
57                                            , "\" in: "
58                                            , fpath
59                                            ])
60            LP.Fail _ _ e
61                → fail ("Failed to parse: " ⧺ fpath ⧺ ": " ⧺ e)
62
63 extMapP ∷ Parser [ (MIMEType, [Text]) ]
64 extMapP = do xs ← P.many (try comment <|> try validLine <|> emptyLine)
65              endOfInput
66              return $ catMaybes xs
67     where
68       isSpc ∷ Char → Bool
69       isSpc c = c ≡ '\x20' ∨ c ≡ '\x09'
70
71       comment ∷ Parser (Maybe (MIMEType, [Text]))
72       comment = do skipWhile isSpc
73                    void $ char '#'
74                    skipWhile (≢ '\x0A')
75                    return Nothing
76
77       validLine ∷ Parser (Maybe (MIMEType, [Text]))
78       validLine = do skipWhile isSpc
79                      mime ← mimeType
80                      skipWhile isSpc
81                      exts ← sepBy extP (skipWhile isSpc)
82                      return $ Just (mime, exts)
83
84       extP ∷ Parser Text
85       extP = decodeUtf8 <$> takeWhile1 (\c → (¬) (isSpc c ∨ c ≡ '\x0A'))
86
87       emptyLine ∷ Parser (Maybe (MIMEType, [Text]))
88       emptyLine = do skipWhile isSpc
89                      void $ char '\x0A'
90                      return Nothing
91
92 compile ∷ Ord k ⇒ [(v, [k])] → Either (k, v, v) (Map k v)
93 compile = go (∅) ∘ concat ∘ map tr
94     where
95       tr ∷ (v, [k]) → [(k, v)]
96       tr (v, ks) = [(k, v) | k ← ks]
97
98       go ∷ Ord k ⇒ Map k v → [(k, v)] → Either (k, v, v) (Map k v)
99       go m []         = Right m
100       go m ((k, v):xs)
101           = case M.insertLookupWithKey' f k v m of
102               (Nothing, m') → go m' xs
103               (Just v0, _ ) → Left (k, v0, v)
104
105       f ∷ k → v → v → v
106       f _ _ = id
107
108 -- |@'serializeExtMap' extMap moduleName variableName@ generates a
109 -- Haskell source code which contains the following things:
110 --
111 -- * A definition of module named @moduleName@.
112 --
113 -- * @variableName :: 'ExtMap'@ whose content is the serialised
114 -- @extMap@.
115 --
116 -- The module "Network.HTTP.Lucu.MIMEType.DefaultExtensionMap" is
117 -- surely generated using this function.
118 serializeExtMap ∷ ExtMap → String → String → String
119 serializeExtMap extMap moduleName variableName
120     = let hsModule  = Module (⊥) (ModuleName moduleName) modPragma
121                       Nothing (Just exports) imports decls
122           modPragma = [ LanguagePragma (⊥) [ name (show OverloadedStrings) ] ]
123           exports   = [ EVar (UnQual (name variableName)) ]
124           imports   = [ ImportDecl (⊥) (ModuleName "Network.HTTP.Lucu.MIMEType")
125                                    False False Nothing Nothing Nothing
126                       , ImportDecl (⊥) (ModuleName "Network.HTTP.Lucu.MIMEType.Guess")
127                                    False False Nothing Nothing Nothing
128                       , ImportDecl (⊥) (ModuleName "Data.Ascii")
129                                    False False Nothing Nothing (Just (False, []))
130                       , ImportDecl (⊥) (ModuleName "Data.Map")
131                                    True False Nothing (Just (ModuleName "M")) Nothing
132                       ]
133           decls     = [ TypeSig (⊥) [name variableName]
134                                     (TyCon (UnQual (name "ExtMap")))
135                       , nameBind (⊥) (name variableName) extMapExp
136                       , InlineSig (⊥) False AlwaysActive (UnQual (name variableName))
137                       ]
138           comment   = concat [ "{- !!! WARNING !!!\n"
139                              , "   This file is automatically generated.\n"
140                              , "   DO NOT EDIT BY HAND OR YOU WILL REGRET -}\n\n"
141                              ]
142           extMapExp = qvar (ModuleName "M") (name "fromList") `app` listE records
143       in
144         comment ⧺ prettyPrint hsModule ⧺ "\n"
145     where
146       records ∷ [Exp]
147       records = map record $ M.assocs extMap
148
149       record ∷ (Text, MIMEType) → Exp
150       record (ext, mime)
151           = tuple [ strE (T.unpack ext)
152                   , function "parseMIMEType" `app` strE (mimeToString mime)
153                   ]
154
155       mimeToString ∷ MIMEType → String
156       mimeToString = A.toString ∘ A.fromAsciiBuilder ∘ printMIMEType