]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/MIMEType/Guess.hs
Use base64-bytestring instead of dataenc
[Lucu.git] / Network / HTTP / Lucu / MIMEType / Guess.hs
index 65bf3a607cc4b8306d5d7114485fb7452817ffe1..39de37e07d68464b8029021f745e956fa236c036 100644 (file)
@@ -1,5 +1,9 @@
--- |MIME Type guesser which guesses by a file extension. This is a
--- poor man's way of guessing MIME Types. It is simple and fast.
+{-# LANGUAGE
+    UnboxedTuples
+  , UnicodeSyntax
+  #-}
+-- |MIME Type guessing by a file extension. This is a poor man's way
+-- of guessing MIME Types. It is simple and fast.
 --
 -- In general you don't have to use this module directly.
 module Network.HTTP.Lucu.MIMEType.Guess
@@ -12,7 +16,6 @@ module Network.HTTP.Lucu.MIMEType.Guess
     where
 
 import qualified Data.ByteString.Lazy.Char8 as B
-import           Data.ByteString.Lazy.Char8 (ByteString)
 import qualified Data.Map as M
 import           Data.Map (Map)
 import           Data.Maybe
@@ -22,9 +25,8 @@ import           Network.HTTP.Lucu.MIMEType
 import           Network.HTTP.Lucu.Parser
 import           Network.HTTP.Lucu.Parser.Http
 import           Network.HTTP.Lucu.Utils
-import           System.IO
 
--- |Map from extension to MIME Type.
+-- |'Data.Map.Map' from extension to MIME Type.
 type ExtMap = Map String MIMEType
 
 -- |Guess the MIME Type of file.
@@ -41,10 +43,13 @@ parseExtMapFile fpath
     = fpath `seq`
       do file <- B.readFile fpath
          case parse (allowEOF extMapP) file of
-           (Success xs, _) -> return $ compile xs
-           (_, input')     -> let near = B.unpack $ B.take 100 input'
-                              in 
-                                fail ("Failed to parse: " ++ fpath ++ " (near: " ++ near ++ ")")
+           (# Success xs, _ #)
+               -> return $ compile xs
+
+           (# _, input' #)
+               -> let near = B.unpack $ B.take 100 input'
+                  in 
+                    fail ("Failed to parse: " ++ fpath ++ " (near: " ++ near ++ ")")
 
 
 extMapP :: Parser [ (MIMEType, [String]) ]
@@ -54,14 +59,14 @@ extMapP = do xs <- many (comment <|> validLine <|> emptyLine)
     where
       spc = oneOf " \t"
 
-      comment = do many spc
-                   char '#'
-                   many $ satisfy (/= '\n')
-                   return Nothing
+      comment = many spc >>
+                char '#' >>
+                ( many $ satisfy (/= '\n') ) >>
+                return Nothing
 
-      validLine = do many spc
+      validLine = do _    <- many spc
                      mime <- mimeTypeP
-                     many spc
+                     _    <- many spc
                      exts <- sepBy token (many spc)
                      return $ Just (mime, exts)
 
@@ -89,10 +94,9 @@ serializeExtMap extMap moduleName variableName
     = let hsModule = HsModule undefined modName (Just exports) imports decls
           modName  = Module moduleName
           exports  = [HsEVar (UnQual (HsIdent variableName))]
-          imports  = [ HsImportDecl undefined (Module "Network.HTTP.Lucu.MIMEType") False Nothing Nothing
+          imports  = [ HsImportDecl undefined (Module "Network.HTTP.Lucu.MIMEType") False Nothing (Just (False, []))
                      , HsImportDecl undefined (Module "Network.HTTP.Lucu.MIMEType.Guess") False Nothing Nothing
                      , HsImportDecl undefined (Module "Data.Map") True (Just (Module "M")) Nothing
-                     , HsImportDecl undefined (Module "Data.Map") False Nothing (Just (False, [HsIAbs (HsIdent "Map")]))
                      ]
           decls    = [ HsTypeSig undefined [HsIdent variableName]
                                      (HsQualType []
@@ -101,9 +105,9 @@ serializeExtMap extMap moduleName variableName
                                   [] (HsUnGuardedRhs extMapExp) []]
                      ]
           extMapExp = HsApp (HsVar (Qual (Module "M") (HsIdent "fromList"))) (HsList records)
-          comment =    "{- !!! WARNING !!!\n"
-                    ++ "   This file is automatically generated.\n"
-                    ++ "   DO NOT EDIT BY HAND OR YOU WILL REGRET -}\n\n"
+          comment   =    "{- !!! WARNING !!!\n"
+                      ++ "   This file is automatically generated.\n"
+                      ++ "   DO NOT EDIT BY HAND OR YOU WILL REGRET -}\n\n"
       in
         comment ++ prettyPrint hsModule ++ "\n"
     where
@@ -115,19 +119,5 @@ serializeExtMap extMap moduleName variableName
           = HsTuple [HsLit (HsString ext), mimeToExp mime]
                     
       mimeToExp :: MIMEType -> HsExp
-      mimeToExp (MIMEType maj min params)
-          = foldl appendParam (HsInfixApp
-                               (HsLit (HsString maj))
-                               (HsQVarOp (UnQual (HsSymbol "</>")))
-                               (HsLit (HsString min))) params
-
-      appendParam :: HsExp -> (String, String) -> HsExp
-      appendParam x param
-          = HsInfixApp x (HsQVarOp (UnQual (HsSymbol "<:>"))) $ paramToExp param
-
-      paramToExp :: (String, String) -> HsExp
-      paramToExp (name, value)
-          = HsInfixApp
-            (HsLit (HsString name))
-            (HsQVarOp (UnQual (HsSymbol "<=>")))
-            (HsLit (HsString value))
\ No newline at end of file
+      mimeToExp mt
+          = HsApp (HsVar (UnQual (HsIdent "read"))) (HsLit (HsString $ show mt))