mime-directory-0.5.2: A library for parsing/printing the text/directory mime type.

Copyright(c) 2008 Mathieu Boespflug
LicenseLGPL
Maintainermboes@tweag.net
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell98

Codec.MIME.ContentType.Text.Directory

Contents

Description

Library for parsing and generating the text/directory mime content type. This library implements all the required mechanisms in RFC 2425, which other libraries may use to implement parsing and generating specific profiles, such as vCard.

Synopsis

Types

type Directory u = [Map Type [Property u]] Source

A directory is a list of groups of semantically related entities. These entities are grouped together in RFC 2425 using BEGIN ... END pairs. Within a group properties are further grouped together by the property types.

data Property u Source

Constructors

Prop 

Instances

data Value u Source

This is sufficient to represent values whose specification is defined in RFC 2425. Values with other specifications can be represented via the IANAValue constructor.

Constructors

URI URI 
Text ByteString 
Date Day 
Time DiffTime 
DateTime UTCTime 
Integer Integer 
Boolean Bool 
Float Float 
IANAValue u

An IANA defined type not part of rfc2425

Instances

data Rfc2425Value Source

Instantiate Value with this phantom type to indicate that property types should be none other than those defined in rfc2425.

type ValueParser u = (Type, [Parameter]) -> ByteString -> [Value u] Source

The type of parsers for property values, for instance to read an integer property, text property, etc.

nakedType :: ByteString -> Type Source

Make a property type without any grouping.

(@@) :: Property u -> ByteString -> Bool Source

Check whether the given property is an instance of the given type.

lookupParameter :: ByteString -> [Parameter] -> Maybe [ByteString] Source

Find the parameter values for a given parameter name.

Encoding/decoding values

decodeValue :: [Parameter] -> ByteString -> ByteString Source

Properties may indicate an encoding, so this decodes the value if need be before parsing.

encodeValue :: [Parameter] -> ByteString -> ByteString Source

Properties may indicate an encoding, so this encodes the value if need be after printing.

escape :: ByteString -> ByteString -> ByteString Source

Escape any occurrence of the characters given as first argument with a backslash. Newlines are always replaced by the two character sequence "\n". The backslash character is always escaped.

Parsing

parseDirectory Source

Arguments

:: ValueParser u

Given a Property Type and a list of parameters, parse a string representation into a Value.

-> ByteString 
-> Directory u 

Produces a map where properties are grouped together using their type as key.

parseDirectory' :: ValueParser u -> ByteString -> [Property u] Source

An alternative version of parseDirectory that produces a list of properties rather than a mapping from property types to properties. Note that here properties in the list are in the same order as in the input string.

fromList :: [Property u] -> Directory u Source

Build a directory from a list of properties.

groupByBeginEnd :: [Property u] -> [[Property u]] Source

Group properties into blocks delimited by begin..end pairs.

Value Parsers

pa_text :: ValueParser u Source

Unescape slashes, newlines and commas.

Value parser combinators

many :: ValueParser u -> ValueParser u Source

Take a parser for single values to a parser for a list of values. This assumes that the separator between values is the "," character, and that values do not contain commas themselves.

Printing