{-# LANGUAGE DeriveDataTypeable , GeneralizedNewtypeDeriving , TemplateHaskell , UnicodeSyntax , ViewPatterns #-} -- |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(..) , extMap , parseExtMap , guessTypeByFileName ) where import Control.Applicative import Control.Monad import Control.Monad.Unicode import Data.Ascii (Ascii) import qualified Data.Ascii as A import Data.Attoparsec.Char8 as P import qualified Data.Map as M import Data.Map (Map) import Data.Maybe import Data.Typeable import Data.Monoid import Data.Monoid.Unicode import Data.Text (Text) import qualified Data.Text as T import Data.Text.Encoding import Language.Haskell.TH.Syntax import Language.Haskell.TH.Quote import Network.HTTP.Lucu.MIMEType import Network.HTTP.Lucu.Parser import Network.HTTP.Lucu.Utils import Prelude.Unicode import System.FilePath -- |A 'Map' from file extensions to 'MIMEType's. newtype ExtMap = ExtMap (Map Text MIMEType) deriving (Eq, Show, Read, Monoid, Typeable) instance Lift ExtMap where lift (ExtMap m) = [| ExtMap $(liftMap liftText lift m) |] -- |'QuasiQuoter' for 'ExtMap' reading Apache @mime.types@. -- -- @ -- m :: 'ExtMap' -- m = ['extMap'| -- # MIME Type Extensions -- application/xhtml+xml xhtml -- image/jpeg jpeg jpg -- image/png png -- image/svg+xml svg -- text/html html -- text/plain txt -- |] -- @ extMap ∷ QuasiQuoter extMap = QuasiQuoter { quoteExp = (lift ∘ parseExtMap =≪) ∘ toAscii , quotePat = const unsupported , quoteType = const unsupported , quoteDec = const unsupported } where toAscii ∷ Monad m ⇒ String → m Ascii toAscii (A.fromChars → Just a) = return a toAscii _ = fail "Malformed extension map" unsupported ∷ Monad m ⇒ m α unsupported = fail "Unsupported usage of extMap quasi-quoter." -- |Parse Apache @mime.types@. parseExtMap ∷ Ascii → ExtMap parseExtMap src = case parseOnly (finishOff extMapP) $ A.toByteString src of Right xs → case compile xs of Right m → ExtMap m Left e → error ("Duplicate extension: " ⧺ show e) Left err → error ("Unparsable extension map: " ⧺ err) extMapP ∷ Parser [(MIMEType, [Text])] extMapP = catMaybes <$> P.many (try comment <|> try validLine <|> emptyLine) where isSpc ∷ Char → Bool isSpc c = c ≡ '\x20' ∨ c ≡ '\x09' comment ∷ Parser (Maybe (MIMEType, [Text])) comment = do skipWhile isSpc void $ char '#' skipWhile (≢ '\x0A') return Nothing validLine ∷ Parser (Maybe (MIMEType, [Text])) validLine = do skipWhile isSpc mime ← mimeType 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 = do skipWhile isSpc void $ 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 -- |Guess the MIME Type of a file. guessTypeByFileName ∷ ExtMap → FilePath → Maybe MIMEType guessTypeByFileName (ExtMap m) fpath = case takeExtension fpath of [] → Nothing (_:ext) → M.lookup (T.pack ext) m