{-# LANGUAGE BangPatterns , 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 ( ExtMap , guessTypeByFileName , parseExtMapFile , serializeExtMap ) where import Control.Applicative import qualified Data.Ascii as A import Data.Attoparsec.Char8 as P import qualified Data.Attoparsec.Lazy as AL import qualified Data.ByteString.Lazy.Char8 as B import qualified Data.Map as M import Data.Map (Map) import Data.Maybe import Data.Text (Text) import qualified Data.Text as T import Data.Text.Encoding import Language.Haskell.Pretty import Language.Haskell.Syntax import Network.HTTP.Lucu.MIMEType import Prelude.Unicode import System.FilePath -- |'Map' from extension to 'MIMEType'. type ExtMap = Map Text MIMEType -- |Guess the MIME Type of file. guessTypeByFileName ∷ ExtMap → FilePath → Maybe MIMEType guessTypeByFileName !extMap !fpath = let ext = T.pack $ takeExtension fpath in M.lookup ext extMap -- |Read an Apache mime.types and parse it. parseExtMapFile ∷ FilePath → IO ExtMap parseExtMapFile fpath = do file ← B.readFile fpath case AL.parse extMapP file of AL.Done _ xs → return $ compile xs AL.Fail _ _ e → fail ("Failed to parse: " ⧺ fpath ⧺ ": " ⧺ e) extMapP ∷ Parser [ (MIMEType, [Text]) ] extMapP = do xs ← P.many (comment <|> validLine <|> emptyLine) endOfInput return $ catMaybes xs where isSpc ∷ Char → Bool isSpc c = c ≡ '\x20' ∨ c ≡ '\x09' comment ∷ Parser (Maybe (MIMEType, [Text])) comment = try $ do skipWhile isSpc _ ← char '#' skipWhile (≢ '\x0A') return Nothing validLine ∷ Parser (Maybe (MIMEType, [Text])) validLine = try $ do skipWhile isSpc mime ← mimeTypeP skipWhile isSpc exts ← sepBy extP (skipWhile isSpc) return $ Just (mime, exts) extP ∷ Parser Text extP = decodeUtf8 <$> takeWhile1 (\c → (¬) (isSpc c ∨ c ≡ '\x0A')) emptyLine ∷ Parser (Maybe (MIMEType, [Text])) emptyLine = try $ do skipWhile isSpc _ ← char '\x0A' return Nothing compile ∷ [ (MIMEType, [Text]) ] → Map Text MIMEType compile = M.fromList ∘ concat ∘ map tr where tr ∷ (MIMEType, [Text]) → [ (Text, MIMEType) ] tr (mime, exts) = [ (ext, mime) | ext ← exts ] -- |@'serializeExtMap' extMap moduleName variableName@ generates a -- Haskell source code which contains the following things: -- -- * A definition of module named @moduleName@. -- -- * @variableName ∷ 'ExtMap'@ whose content is a serialization of -- @extMap@. -- -- The module "Network.HTTP.Lucu.MIMEType.DefaultExtensionMap" is -- surely generated using this function. serializeExtMap ∷ ExtMap → String → String → String serializeExtMap extMap moduleName variableName = let hsModule = HsModule (⊥) modName (Just exports) imports decls modName = Module moduleName exports = [HsEVar (UnQual (HsIdent variableName))] imports = [ HsImportDecl (⊥) (Module "Network.HTTP.Lucu.MIMEType") False Nothing Nothing , HsImportDecl (⊥) (Module "Network.HTTP.Lucu.MIMEType.Guess") False Nothing Nothing , HsImportDecl (⊥) (Module "Data.Ascii") True (Just (Module "A")) Nothing , HsImportDecl (⊥) (Module "Data.Map") True (Just (Module "M")) Nothing , HsImportDecl (⊥) (Module "Data.Text") True (Just (Module "T")) Nothing ] decls = [ HsTypeSig (⊥) [HsIdent variableName] (HsQualType [] (HsTyCon (UnQual (HsIdent "ExtMap")))) , HsFunBind [HsMatch (⊥) (HsIdent 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" in comment ++ prettyPrint hsModule ++ "\n" where records ∷ [HsExp] records = map record $ M.assocs extMap record ∷ (Text, MIMEType) → HsExp record (ext, mime) = HsTuple [ HsApp (HsVar (Qual (Module "T") (HsIdent "pack"))) (HsLit (HsString (T.unpack ext))) , mimeToExp mime ] mimeToExp ∷ MIMEType → HsExp mimeToExp mt = HsApp (HsVar (UnQual (HsIdent "parseMIMEType"))) (HsParen (HsApp (HsVar (Qual (Module "A") (HsIdent "unsafeFromString"))) (HsLit (HsString $ A.toString $ printMIMEType mt))))