X-Git-Url: http://git.cielonegro.org/gitweb.cgi?p=Lucu.git;a=blobdiff_plain;f=Network%2FHTTP%2FLucu%2FMIMEType%2FGuess.hs;h=05d0cd606f383eccdbef688a39dfa4f1e215b3d5;hp=86d7df6ef48277a798bd6e46145f77222097583d;hb=90fca0675b1694e69b8e431c989343855cbd125d;hpb=ece223c516e66223ef1d5d8e6bbe4054a235d983 diff --git a/Network/HTTP/Lucu/MIMEType/Guess.hs b/Network/HTTP/Lucu/MIMEType/Guess.hs index 86d7df6..05d0cd6 100644 --- a/Network/HTTP/Lucu/MIMEType/Guess.hs +++ b/Network/HTTP/Lucu/MIMEType/Guess.hs @@ -1,98 +1,127 @@ {-# LANGUAGE - UnicodeSyntax + DeriveDataTypeable + , GeneralizedNewtypeDeriving + , MultiParamTypeClasses + , 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(..) + , extMap , guessTypeByFileName - - , parseExtMapFile - , serializeExtMap ) where import Control.Applicative -import qualified Data.Ascii as A -import Data.Attoparsec.Char8 as P +import Data.Attoparsec.Char8 import qualified Data.Attoparsec.Lazy as LP -import qualified Data.ByteString.Lazy.Char8 as B +import qualified Data.ByteString.Lazy.Char8 as Lazy +import Data.Convertible.Base +import Data.Convertible.Instances.Text () +import Data.Default import qualified Data.Map as M import Data.Map (Map) -import Data.Maybe +import Data.Typeable +import Data.List +import Data.Monoid 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 Language.Haskell.TH.Syntax +import Language.Haskell.TH.Quote import Network.HTTP.Lucu.MIMEType +import Network.HTTP.Lucu.OrphanInstances () +import Network.HTTP.Lucu.Parser import Prelude.Unicode import System.FilePath -- |A 'Map' from file extensions to 'MIMEType's. -type ExtMap = Map Text MIMEType +newtype ExtMap + = ExtMap (Map Text MIMEType) + deriving (Eq, Show, Read, Monoid, Typeable) --- |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 +instance Lift ExtMap where + lift (ExtMap m) = [| ExtMap $(lift m) |] --- |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 +-- |'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 ∘ Lazy.pack + , quotePat = const unsupported + , quoteType = const unsupported + , quoteDec = const unsupported + } where - isSpc ∷ Char → Bool - isSpc c = c ≡ '\x20' ∨ c ≡ '\x09' + parseExtMap ∷ Lazy.ByteString → ExtMap + parseExtMap = convertUnsafe - comment ∷ Parser (Maybe (MIMEType, [Text])) - comment = try $ - do skipWhile isSpc - _ ← char '#' - skipWhile (≢ '\x0A') - return Nothing + unsupported ∷ Monad m ⇒ m α + unsupported = fail "Unsupported usage of extMap quasi-quoter." - validLine ∷ Parser (Maybe (MIMEType, [Text])) - validLine = try $ - do skipWhile isSpc - mime ← mimeTypeP - skipWhile isSpc - exts ← sepBy extP (skipWhile isSpc) - return $ Just (mime, exts) +instance ConvertAttempt Lazy.ByteString ExtMap where + convertAttempt src + = case LP.parse pairs src of + LP.Fail _ eCtx e + → fail $ "Unparsable extension map: " + ⊕ intercalate ", " eCtx + ⊕ ": " + ⊕ e + LP.Done _ xs + → case compile xs of + Right m → return $ ExtMap m + Left e → fail $ "Duplicate extension: " ⊕ show e + where + pairs ∷ Parser [(MIMEType, [Text])] + pairs = do skipMany linebreak + xs ← sepBy pair (skipMany1 linebreak) + skipMany linebreak + endOfInput + return xs + + "pairs" - extP ∷ Parser Text - extP = decodeUtf8 <$> takeWhile1 (\c → (¬) (isSpc c ∨ c ≡ '\x0A')) + pair ∷ Parser (MIMEType, [Text]) + pair = do skipSpace + mime ← def + skipSpace1 + exts ← sepBy1 ext $ skipWhile1 (≡ '\x20') + return (mime, exts) + + "pair" - emptyLine ∷ Parser (Maybe (MIMEType, [Text])) - emptyLine = try $ - do skipWhile isSpc - _ ← char '\x0A' - return Nothing + ext ∷ Parser Text + ext = (decodeUtf8 <$> takeWhile1 isAlphaNum) + + "ext" + + linebreak ∷ Parser () + linebreak + = ( endOfLine + <|> + try (skipSpace *> char '#' *> skipManyTill anyChar endOfLine) + ) + + "linebreak" compile ∷ Ord k ⇒ [(v, [k])] → Either (k, v, v) (Map k v) -compile = go (∅) ∘ concat ∘ map tr +compile = go (∅) ∘ concat ∘ (tr <$>) where tr ∷ (v, [k]) → [(k, v)] tr (v, ks) = [(k, v) | k ← ks] @@ -107,52 +136,9 @@ compile = go (∅) ∘ concat ∘ map tr 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 - , InlineSig (⊥) False AlwaysActive (UnQual (name variableName)) - ] - 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 +-- |Guess the MIME Type of a file. +guessTypeByFileName ∷ ExtMap → FilePath → Maybe MIMEType +guessTypeByFileName (ExtMap m) fpath + = case takeExtension fpath of + [] → Nothing + (_:ext) → M.lookup (cs ext) m