X-Git-Url: http://git.cielonegro.org/gitweb.cgi?a=blobdiff_plain;f=Network%2FHTTP%2FLucu%2FMIMEType%2FGuess.hs;h=10c11e41c128cc7446082e0f3e5ed810f4a92cf6;hb=b1fac0a2cb1cafa008c0efa8ae4e14afbee0927f;hp=eabc06ffe5808c9ee6c7b420172173730fb1534a;hpb=1789cee5ee66d2f7f2b26280be2f13eac4df7980;p=Lucu.git diff --git a/Network/HTTP/Lucu/MIMEType/Guess.hs b/Network/HTTP/Lucu/MIMEType/Guess.hs index eabc06f..10c11e4 100644 --- a/Network/HTTP/Lucu/MIMEType/Guess.hs +++ b/Network/HTTP/Lucu/MIMEType/Guess.hs @@ -1,8 +1,8 @@ {-# LANGUAGE UnicodeSyntax #-} --- |MIME Type guessing by a file extension. This is a poor man's way --- of guessing MIME Types. It is simple and fast. +-- |Guessing MIME Types by file extensions. It's not always accurate +-- but simple and fast. -- -- In general you don't have to use this module directly. module Network.HTTP.Lucu.MIMEType.Guess @@ -14,6 +14,7 @@ module Network.HTTP.Lucu.MIMEType.Guess ) where import Control.Applicative +import Control.Monad import qualified Data.Ascii as A import Data.Attoparsec.Char8 as P import qualified Data.Attoparsec.Lazy as LP @@ -30,24 +31,25 @@ import Language.Haskell.Exts.Extension import Language.Haskell.Exts.Pretty import Language.Haskell.Exts.Syntax import Network.HTTP.Lucu.MIMEType +import Network.HTTP.Lucu.Parser import Prelude.Unicode import System.FilePath --- |'Map' from extension to 'MIMEType'. +-- |A 'Map' from file extensions to 'MIMEType's. type ExtMap = Map Text MIMEType --- |Guess the MIME Type of file. +-- |Guess the MIME Type of a file. guessTypeByFileName ∷ ExtMap → FilePath → Maybe MIMEType -guessTypeByFileName extMap fpath +guessTypeByFileName em fpath = case takeExtension fpath of [] → Nothing - (_:ext) → M.lookup (T.pack ext) extMap + (_:ext) → M.lookup (T.pack ext) em -- |Read an Apache mime.types and parse it. parseExtMapFile ∷ FilePath → IO ExtMap parseExtMapFile fpath = do file ← B.readFile fpath - case LP.parse extMapP file of + case LP.parse (finishOff extMap) file of LP.Done _ xs → case compile xs of Right m → return m @@ -59,25 +61,21 @@ parseExtMapFile fpath LP.Fail _ _ e → fail ("Failed to parse: " ⧺ fpath ⧺ ": " ⧺ e) -extMapP ∷ Parser [ (MIMEType, [Text]) ] -extMapP = do xs ← P.many (comment <|> validLine <|> emptyLine) - endOfInput - return $ catMaybes xs +extMap ∷ Parser [ (MIMEType, [Text]) ] +extMap = catMaybes <$> P.many (try comment <|> try validLine <|> emptyLine) where isSpc ∷ Char → Bool isSpc c = c ≡ '\x20' ∨ c ≡ '\x09' comment ∷ Parser (Maybe (MIMEType, [Text])) - comment = try $ - do skipWhile isSpc - _ ← char '#' + comment = do skipWhile isSpc + void $ char '#' skipWhile (≢ '\x0A') return Nothing validLine ∷ Parser (Maybe (MIMEType, [Text])) - validLine = try $ - do skipWhile isSpc - mime ← mimeTypeP + validLine = do skipWhile isSpc + mime ← mimeType skipWhile isSpc exts ← sepBy extP (skipWhile isSpc) return $ Just (mime, exts) @@ -86,9 +84,8 @@ extMapP = do xs ← P.many (comment <|> validLine <|> emptyLine) extP = decodeUtf8 <$> takeWhile1 (\c → (¬) (isSpc c ∨ c ≡ '\x0A')) emptyLine ∷ Parser (Maybe (MIMEType, [Text])) - emptyLine = try $ - do skipWhile isSpc - _ ← char '\x0A' + emptyLine = do skipWhile isSpc + void $ char '\x0A' return Nothing compile ∷ Ord k ⇒ [(v, [k])] → Either (k, v, v) (Map k v) @@ -112,13 +109,13 @@ compile = go (∅) ∘ concat ∘ map tr -- -- * A definition of module named @moduleName@. -- --- * @variableName :: 'ExtMap'@ whose content is a serialization of --- @extMap@. +-- * @variableName :: 'ExtMap'@ whose content is the serialised +-- @extMap@. -- -- The module "Network.HTTP.Lucu.MIMEType.DefaultExtensionMap" is -- surely generated using this function. serializeExtMap ∷ ExtMap → String → String → String -serializeExtMap extMap moduleName variableName +serializeExtMap em moduleName variableName = let hsModule = Module (⊥) (ModuleName moduleName) modPragma Nothing (Just exports) imports decls modPragma = [ LanguagePragma (⊥) [ name (show OverloadedStrings) ] ] @@ -135,6 +132,7 @@ serializeExtMap extMap moduleName variableName decls = [ TypeSig (⊥) [name variableName] (TyCon (UnQual (name "ExtMap"))) , nameBind (⊥) (name variableName) extMapExp + , InlineSig (⊥) False AlwaysActive (UnQual (name variableName)) ] comment = concat [ "{- !!! WARNING !!!\n" , " This file is automatically generated.\n" @@ -145,7 +143,7 @@ serializeExtMap extMap moduleName variableName comment ⧺ prettyPrint hsModule ⧺ "\n" where records ∷ [Exp] - records = map record $ M.assocs extMap + records = map record $ M.assocs em record ∷ (Text, MIMEType) → Exp record (ext, mime)