{-# LANGUAGE UnicodeSyntax #-} -- |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 ( 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 LP import qualified Data.ByteString.Lazy.Char8 as B import qualified Data.Map as M import Data.Map (Map) import Data.Maybe import Data.Monoid.Unicode import Data.Text (Text) import qualified Data.Text as T import Data.Text.Encoding import Language.Haskell.Exts.Build import Language.Haskell.Exts.Extension import Language.Haskell.Exts.Pretty import Language.Haskell.Exts.Syntax import Network.HTTP.Lucu.MIMEType import Prelude.Unicode import System.FilePath -- |A 'Map' from file extensions to 'MIMEType's. type ExtMap = Map Text MIMEType -- |Guess the MIME Type of a file. guessTypeByFileName ∷ ExtMap → FilePath → Maybe MIMEType guessTypeByFileName extMap fpath = case takeExtension fpath of [] → Nothing (_:ext) → M.lookup (T.pack ext) extMap -- |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 LP.Done _ xs → case compile xs of Right m → return m Left e → fail (concat [ "Duplicate extension \"" , show e , "\" in: " , 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 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 ∷ Ord k ⇒ [(v, [k])] → Either (k, v, v) (Map k v) compile = go (∅) ∘ concat ∘ map tr where tr ∷ (v, [k]) → [(k, v)] tr (v, ks) = [(k, v) | k ← ks] go ∷ Ord k ⇒ Map k v → [(k, v)] → Either (k, v, v) (Map k v) go m [] = Right m go m ((k, v):xs) = case M.insertLookupWithKey' f k v m of (Nothing, m') → go m' xs (Just v0, _ ) → Left (k, v0, v) f ∷ k → v → v → v f _ _ = id -- |@'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 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 = let hsModule = Module (⊥) (ModuleName moduleName) modPragma Nothing (Just exports) imports decls modPragma = [ LanguagePragma (⊥) [ name (show OverloadedStrings) ] ] exports = [ EVar (UnQual (name variableName)) ] imports = [ ImportDecl (⊥) (ModuleName "Network.HTTP.Lucu.MIMEType") False False Nothing Nothing Nothing , ImportDecl (⊥) (ModuleName "Network.HTTP.Lucu.MIMEType.Guess") False False Nothing Nothing Nothing , ImportDecl (⊥) (ModuleName "Data.Ascii") False False Nothing Nothing (Just (False, [])) , ImportDecl (⊥) (ModuleName "Data.Map") True False Nothing (Just (ModuleName "M")) Nothing ] decls = [ TypeSig (⊥) [name variableName] (TyCon (UnQual (name "ExtMap"))) , nameBind (⊥) (name variableName) extMapExp ] comment = concat [ "{- !!! WARNING !!!\n" , " This file is automatically generated.\n" , " DO NOT EDIT BY HAND OR YOU WILL REGRET -}\n\n" ] extMapExp = qvar (ModuleName "M") (name "fromList") `app` listE records in comment ⧺ prettyPrint hsModule ⧺ "\n" where records ∷ [Exp] records = map record $ M.assocs extMap record ∷ (Text, MIMEType) → Exp record (ext, mime) = tuple [ strE (T.unpack ext) , function "parseMIMEType" `app` strE (mimeToString mime) ] mimeToString ∷ MIMEType → String mimeToString = A.toString ∘ A.fromAsciiBuilder ∘ printMIMEType