Copyright | (c) Peter Thiemann 20012002 (c) Bjorn Bringert 2005-2006 |
---|---|
License | BSD-style |
Maintainer | Anders Kaseorg <andersk@mit.edu> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Network.Multipart.Header
Description
Parsing of HTTP headers (name, value pairs) Partly based on code from WASHMail.
Synopsis
- type Headers = [(HeaderName, String)]
- newtype HeaderName = HeaderName String
- class HeaderValue a where
- parseHeaderValue :: Parser a
- prettyHeaderValue :: a -> String
- pHeaders :: Parser Headers
- data ContentType = ContentType {}
- getContentType :: MonadFail m => Headers -> m ContentType
- parseContentType :: MonadFail m => String -> m ContentType
- showContentType :: ContentType -> String
- data ContentTransferEncoding = ContentTransferEncoding String
- getContentTransferEncoding :: MonadFail m => Headers -> m ContentTransferEncoding
- data ContentDisposition = ContentDisposition String [(String, String)]
- getContentDisposition :: MonadFail m => Headers -> m ContentDisposition
- parseM :: MonadFail m => Parser a -> SourceName -> String -> m a
- caseInsensitiveEq :: String -> String -> Bool
- caseInsensitiveCompare :: String -> String -> Ordering
- lexeme :: Parser a -> Parser a
- ws1 :: Parser Char
- p_token :: Parser String
Headers
type Headers = [(HeaderName, String)] Source #
HTTP headers.
newtype HeaderName Source #
A string with case insensitive equality and comparisons.
Constructors
HeaderName String |
Instances
Eq HeaderName Source # | |
Defined in Network.Multipart.Header | |
Ord HeaderName Source # | |
Defined in Network.Multipart.Header Methods compare :: HeaderName -> HeaderName -> Ordering # (<) :: HeaderName -> HeaderName -> Bool # (<=) :: HeaderName -> HeaderName -> Bool # (>) :: HeaderName -> HeaderName -> Bool # (>=) :: HeaderName -> HeaderName -> Bool # max :: HeaderName -> HeaderName -> HeaderName # min :: HeaderName -> HeaderName -> HeaderName # | |
Show HeaderName Source # | |
Defined in Network.Multipart.Header Methods showsPrec :: Int -> HeaderName -> ShowS # show :: HeaderName -> String # showList :: [HeaderName] -> ShowS # |
class HeaderValue a where Source #
Instances
HeaderValue ContentDisposition Source # | |
Defined in Network.Multipart.Header Methods | |
HeaderValue ContentTransferEncoding Source # | |
Defined in Network.Multipart.Header | |
HeaderValue ContentType Source # | |
Defined in Network.Multipart.Header Methods |
Content-type
data ContentType Source #
A MIME media type value.
The Show
instance is derived automatically.
Use showContentType
to obtain the standard
string representation.
See http://www.ietf.org/rfc/rfc2046.txt for more
information about MIME media types.
Constructors
ContentType | |
Fields
|
Instances
Eq ContentType Source # | |
Defined in Network.Multipart.Header | |
Ord ContentType Source # | |
Defined in Network.Multipart.Header Methods compare :: ContentType -> ContentType -> Ordering # (<) :: ContentType -> ContentType -> Bool # (<=) :: ContentType -> ContentType -> Bool # (>) :: ContentType -> ContentType -> Bool # (>=) :: ContentType -> ContentType -> Bool # max :: ContentType -> ContentType -> ContentType # min :: ContentType -> ContentType -> ContentType # | |
Read ContentType Source # | |
Defined in Network.Multipart.Header Methods readsPrec :: Int -> ReadS ContentType # readList :: ReadS [ContentType] # readPrec :: ReadPrec ContentType # readListPrec :: ReadPrec [ContentType] # | |
Show ContentType Source # | |
Defined in Network.Multipart.Header Methods showsPrec :: Int -> ContentType -> ShowS # show :: ContentType -> String # showList :: [ContentType] -> ShowS # | |
HeaderValue ContentType Source # | |
Defined in Network.Multipart.Header Methods |
getContentType :: MonadFail m => Headers -> m ContentType Source #
parseContentType :: MonadFail m => String -> m ContentType Source #
Parse the standard representation of a content-type.
If the input cannot be parsed, this function calls
MonadFail
with a (hopefully) informative error message.
showContentType :: ContentType -> String Source #
Content-transfer-encoding
data ContentTransferEncoding Source #
Constructors
ContentTransferEncoding String |
Instances
getContentTransferEncoding :: MonadFail m => Headers -> m ContentTransferEncoding Source #
Content-disposition
data ContentDisposition Source #
Constructors
ContentDisposition String [(String, String)] |
Instances
getContentDisposition :: MonadFail m => Headers -> m ContentDisposition Source #