purebred-email-0.5.1: types and parser for email messages (including MIME)
Safe HaskellNone
LanguageHaskell2010

Data.MIME.Parameter

Description

MIME parameters, per RFC 2045 and RFC 2231.

RFC 2231 defines a mechanism for parameter continuations (for long parameters), encoding of non-ASCII characters, and charset and language annotation. The most common use of these capabilities is in the Content-Disposition header, for the filename parameter.

This module provides types and functions for working with parameters.

Synopsis

Documentation

newtype Parameters Source #

Header parameters. Used for some headers including Content-Type and Content-Disposition. This type handles parameter continuations and optional charset and language information (RFC 2231).

Constructors

Parameters [(CI ByteString, ByteString)] 

Instances

Instances details
Eq Parameters Source # 
Instance details

Defined in Data.MIME.Parameter

Show Parameters Source # 
Instance details

Defined in Data.MIME.Parameter

Generic Parameters Source # 
Instance details

Defined in Data.MIME.Parameter

Associated Types

type Rep Parameters :: Type -> Type #

Semigroup Parameters Source # 
Instance details

Defined in Data.MIME.Parameter

Monoid Parameters Source # 
Instance details

Defined in Data.MIME.Parameter

NFData Parameters Source # 
Instance details

Defined in Data.MIME.Parameter

Methods

rnf :: Parameters -> () #

Ixed Parameters Source # 
Instance details

Defined in Data.MIME.Parameter

At Parameters Source # 
Instance details

Defined in Data.MIME.Parameter

HasParameters Parameters Source # 
Instance details

Defined in Data.MIME.Parameter

type Rep Parameters Source # 
Instance details

Defined in Data.MIME.Parameter

type Rep Parameters = D1 ('MetaData "Parameters" "Data.MIME.Parameter" "purebred-email-0.5.1-Hdwf0dbWkKzBtTQxV1nBC4" 'True) (C1 ('MetaCons "Parameters" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(CI ByteString, ByteString)])))
type Index Parameters Source # 
Instance details

Defined in Data.MIME.Parameter

type IxValue Parameters Source # 
Instance details

Defined in Data.MIME.Parameter

parameterList :: HasParameters a => Lens' a RawParameters Source #

parameter :: HasParameters a => CI ByteString -> Lens' a (Maybe EncodedParameterValue) Source #

Access parameter value. Continuations, encoding and charset are processed.

rawParameter :: HasParameters a => CI ByteString -> Traversal' a ByteString Source #

Raw parameter. The key is used as-is. No processing of continuations, encoding or charset is performed.

newParameter :: Cons s s Char Char => s -> EncodedParameterValue Source #

Convenience function to construct a parameter value. If you need to to specify language, use the ParameterValue constructor directly.

data ParameterValue cs a Source #

Constructors

ParameterValue (Maybe cs) (Maybe (CI ByteString)) a 

Instances

Instances details
IsString DecodedParameterValue Source #

Parameter value with no language.

Instance details

Defined in Data.MIME.Parameter

IsString EncodedParameterValue Source #

Parameter value with no language, encoded either in us-ascii or @utf-8.

Instance details

Defined in Data.MIME.Parameter

HasCharset EncodedParameterValue Source #

The default charset us-ascii is implied by the abstract of RFC 2231 which states: /This memo defines … a means to specify parameter values in character sets other than US-ASCII/.

When encoding, 'utf-8' is always used, but if the whole string contains only ASCII characters then the charset declaration is omitted (so that it can be encoded as a non-extended parameter).

Instance details

Defined in Data.MIME.Parameter

Associated Types

type Decoded EncodedParameterValue Source #

(Eq cs, Eq a) => Eq (ParameterValue cs a) Source # 
Instance details

Defined in Data.MIME.Parameter

Methods

(==) :: ParameterValue cs a -> ParameterValue cs a -> Bool #

(/=) :: ParameterValue cs a -> ParameterValue cs a -> Bool #

(Show cs, Show a) => Show (ParameterValue cs a) Source # 
Instance details

Defined in Data.MIME.Parameter

Generic (ParameterValue cs a) Source # 
Instance details

Defined in Data.MIME.Parameter

Associated Types

type Rep (ParameterValue cs a) :: Type -> Type #

Methods

from :: ParameterValue cs a -> Rep (ParameterValue cs a) x #

to :: Rep (ParameterValue cs a) x -> ParameterValue cs a #

(NFData cs, NFData a) => NFData (ParameterValue cs a) Source # 
Instance details

Defined in Data.MIME.Parameter

Methods

rnf :: ParameterValue cs a -> () #

type Decoded EncodedParameterValue Source # 
Instance details

Defined in Data.MIME.Parameter

type Rep (ParameterValue cs a) Source # 
Instance details

Defined in Data.MIME.Parameter

type Rep (ParameterValue cs a) = D1 ('MetaData "ParameterValue" "Data.MIME.Parameter" "purebred-email-0.5.1-Hdwf0dbWkKzBtTQxV1nBC4" 'False) (C1 ('MetaCons "ParameterValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe cs)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (CI ByteString))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))))