purebred-email-0.4.1: types and parser for email messages (including MIME)

Safe HaskellNone
LanguageHaskell2010

Data.RFC5322.Internal

Contents

Synopsis

Case-insensitive value parsers

ci :: FoldCase s => Parser s -> Parser (CI s) Source #

Modify a parser to produce a case-insensitive value

data CI s #

Instances
IsString EncodedParameterValue

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

Instance details

Defined in Data.MIME.Parameter

Methods

fromString :: String -> EncodedParameterValue

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 :: Type Source #

Methods

charsetName :: Getter EncodedParameterValue (Maybe CharsetName) Source #

charsetData :: Getter EncodedParameterValue ByteString Source #

charsetDecoded :: AsCharsetError e => CharsetLookup -> forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Profunctor p, Contravariant f) => Optic' p f EncodedParameterValue (Either e (Decoded EncodedParameterValue)) Source #

charsetEncode :: Decoded EncodedParameterValue -> EncodedParameterValue Source #

Eq s => Eq (CI s) 
Instance details

Defined in Data.CaseInsensitive.Internal

Methods

(==) :: CI s -> CI s -> Bool

(/=) :: CI s -> CI s -> Bool

Data s => Data (CI s) 
Instance details

Defined in Data.CaseInsensitive.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CI s -> c (CI s)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CI s)

toConstr :: CI s -> Constr

dataTypeOf :: CI s -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (CI s))

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CI s))

gmapT :: (forall b. Data b => b -> b) -> CI s -> CI s

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CI s -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CI s -> r

gmapQ :: (forall d. Data d => d -> u) -> CI s -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> CI s -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CI s -> m (CI s)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CI s -> m (CI s)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CI s -> m (CI s)

Ord s => Ord (CI s) 
Instance details

Defined in Data.CaseInsensitive.Internal

Methods

compare :: CI s -> CI s -> Ordering

(<) :: CI s -> CI s -> Bool

(<=) :: CI s -> CI s -> Bool

(>) :: CI s -> CI s -> Bool

(>=) :: CI s -> CI s -> Bool

max :: CI s -> CI s -> CI s

min :: CI s -> CI s -> CI s

(Read s, FoldCase s) => Read (CI s) 
Instance details

Defined in Data.CaseInsensitive.Internal

Methods

readsPrec :: Int -> ReadS (CI s)

readList :: ReadS [CI s]

readPrec :: ReadPrec (CI s)

readListPrec :: ReadPrec [CI s]

Show s => Show (CI s) 
Instance details

Defined in Data.CaseInsensitive.Internal

Methods

showsPrec :: Int -> CI s -> ShowS

show :: CI s -> String

showList :: [CI s] -> ShowS

(IsString s, FoldCase s) => IsString (CI s) 
Instance details

Defined in Data.CaseInsensitive.Internal

Methods

fromString :: String -> CI s

Semigroup s => Semigroup (CI s) 
Instance details

Defined in Data.CaseInsensitive.Internal

Methods

(<>) :: CI s -> CI s -> CI s

sconcat :: NonEmpty (CI s) -> CI s

stimes :: Integral b => b -> CI s -> CI s

Monoid s => Monoid (CI s) 
Instance details

Defined in Data.CaseInsensitive.Internal

Methods

mempty :: CI s

mappend :: CI s -> CI s -> CI s

mconcat :: [CI s] -> CI s

FoldCase (CI s) 
Instance details

Defined in Data.CaseInsensitive.Internal

Methods

foldCase :: CI s -> CI s

foldCaseList :: [CI s] -> [CI s]

NFData s => NFData (CI s) 
Instance details

Defined in Data.CaseInsensitive.Internal

Methods

rnf :: CI s -> ()

Hashable s => Hashable (CI s) 
Instance details

Defined in Data.CaseInsensitive.Internal

Methods

hashWithSalt :: Int -> CI s -> Int

hash :: CI s -> Int

type Decoded EncodedParameterValue Source # 
Instance details

Defined in Data.MIME.Parameter

original :: CI s -> s #

Abstract character parsers

wsp :: CharParsing f s a => f s a Source #

optionalFWS :: (Alternative (f s), CharParsing f s a, Monoid s) => f s s Source #

FWS collapsed to a single SPACE character, or empty string

optionalCFWS :: (Alternative (f s), CharParsing f s a, SM s) => f s s Source #

CFWS collapsed to a single SPACE character, or empty string

crlf :: Alternative (f s) => CharParsing f s a => f s () Source #

Either CRLF or LF (lots of mail programs transform CRLF to LF)

vchar :: CharParsing f s a => f s a Source #

word :: (Alternative (f s), CharParsing f s a, SM s) => f s s Source #

quotedString :: (Alternative (f s), CharParsing f s a, SM s) => f s s Source #

dotAtom :: (Alternative (f s), CharParsing f s a, SM s) => f s (NonEmpty s) Source #

localPart :: (Alternative (f s), CharParsing f s a, SM s) => f s s Source #

domainLiteral :: (Alternative (f s), CharParsing f s a, SM s) => f s s Source #

class IsChar a where Source #

Methods

toChar :: a -> Char Source #

fromChar :: Char -> a Source #

Instances
IsChar Char Source # 
Instance details

Defined in Data.RFC5322.Internal

Methods

toChar :: Char -> Char Source #

fromChar :: Char -> Char Source #

IsChar Word8 Source # 
Instance details

Defined in Data.RFC5322.Internal

Methods

toChar :: Word8 -> Char Source #

fromChar :: Char -> Word8 Source #

class IsChar a => CharParsing f s a | s -> a, a -> f s where Source #

Methods

singleton :: Char -> s Source #

satisfy :: (Char -> Bool) -> f s a Source #

takeWhile :: (Char -> Bool) -> f s s Source #

takeWhile1 :: (Char -> Bool) -> f s s Source #

Instances
CharParsing Parser ByteString Word8 Source # 
Instance details

Defined in Data.RFC5322.Internal

Methods

singleton :: Char -> ByteString Source #

satisfy :: (Char -> Bool) -> Parser ByteString Word8 Source #

takeWhile :: (Char -> Bool) -> Parser ByteString ByteString Source #

takeWhile1 :: (Char -> Bool) -> Parser ByteString ByteString Source #

CharParsing Parser Text Char Source # 
Instance details

Defined in Data.RFC5322.Internal

Methods

singleton :: Char -> Text Source #

satisfy :: (Char -> Bool) -> Parser Text Char Source #

takeWhile :: (Char -> Bool) -> Parser Text Text Source #

takeWhile1 :: (Char -> Bool) -> Parser Text Text Source #

type SM a = Monoid a Source #

Constraint synonym to handle the Semigroup Monoid Proposal transition gracefully.

Helpers for building parsers

isAtext :: IsChar c => c -> Bool Source #

isQtext :: IsChar c => c -> Bool Source #

isVchar :: IsChar c => c -> Bool Source #

isWsp :: IsChar c => c -> Bool Source #

Semigroup and monoid folding combinators

(<<>>) :: (Semigroup m, Applicative f) => f m -> f m -> f m Source #

Combine two semigroup parsers into one

foldMany :: (Monoid m, Alternative f) => f m -> f m Source #

Parse zero or more values and fold them

foldMany1 :: (Semigroup m, Alternative f) => f m -> f m Source #

Parse one or more values and fold them

foldMany1Sep :: (Semigroup m, Alternative f) => m -> f m -> f m Source #

Parse one or more values and fold them with a separating element

General parsers and combinators

skipTill :: Parser a -> Parser () Source #

Skip until the given parser succeeds

@ λ> parseOnly (string "foo" *> skipTill (string ".") *> endOfInput) "foobar." Right () @

takeTill' :: Parser a -> Parser ByteString Source #

Take until the parser matches (fails if it never matches).

@ λ> parseOnly (takeTill' (string "bar") <* endOfInput) "foobar" Right "foo" @

Efficient string search

skipTillString :: ByteString -> Parser () Source #

Efficient skip, using Boyer-Moore to locate the pattern.

@ λ> parseOnly (string "foo" *> skipTillString "." *> endOfInput) "foobar." Right () @

takeTillString :: ByteString -> Parser ByteString Source #

Efficient take, using Boyer-Moore to locate the pattern.

@ λ> parseOnly (takeTillString "bar" <* endOfInput) "foobar" Right "foo" @