Portability | non-portable |
---|---|
Stability | experimental |
Maintainer | mboes@tweag.net |
Codec.MIME.ContentType.Text.Directory
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.
- type Directory u = [Map Type [Property u]]
- data Property u = Prop {
- prop_type :: Type
- prop_parameters :: [Parameter]
- prop_value :: Value u
- data Type = Type {}
- data Parameter = Param {}
- data Value u
- data Rfc2425Value
- class PrintValue a where
- printValue :: a -> ByteString
- type ValueParser u = (Type, [Parameter]) -> ByteString -> [Value u]
- nakedType :: ByteString -> Type
- (@@) :: Property u -> ByteString -> Bool
- lookupParameter :: ByteString -> [Parameter] -> Maybe [ByteString]
- decodeValue :: [Parameter] -> ByteString -> ByteString
- encodeValue :: [Parameter] -> ByteString -> ByteString
- escape :: ByteString -> ByteString -> ByteString
- parseDirectory :: ValueParser u -> ByteString -> Directory u
- parseDirectory' :: ValueParser u -> ByteString -> [Property u]
- fromList :: [Property u] -> Directory u
- groupByBeginEnd :: [Property u] -> [[Property u]]
- pa_URI :: ValueParser u
- pa_text :: ValueParser u
- pa_date :: ValueParser u
- pa_time :: ValueParser u
- pa_dateTime :: ValueParser u
- pa_integer :: ValueParser u
- pa_boolean :: ValueParser u
- pa_float :: ValueParser u
- pa_textList :: ValueParser u
- many :: ValueParser u -> ValueParser u
- printDirectory :: PrintValue u => Directory u -> ByteString
- printDirectory' :: PrintValue u => [Property u] -> ByteString
- printProperty :: PrintValue u => Property u -> ByteString
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.
Constructors
Prop | |
Fields
|
Constructors
Type | |
Fields |
Constructors
Param | |
Fields
|
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
Eq u => Eq (Value u) | |
Show u => Show (Value u) | |
PrintValue u => PrintValue (Value u) |
data Rfc2425Value Source
Instantiate Value with this phantom type to indicate that property types should be none other than those defined in rfc2425.
Instances
class PrintValue a whereSource
Methods
printValue :: a -> ByteStringSource
Instances
PrintValue Rfc2425Value | |
PrintValue u => PrintValue (Value u) |
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 -> TypeSource
Make a property type without any grouping.
(@@) :: Property u -> ByteString -> BoolSource
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 -> ByteStringSource
encodeValue :: [Parameter] -> ByteString -> ByteStringSource
escape :: ByteString -> ByteString -> ByteStringSource
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
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.
groupByBeginEnd :: [Property u] -> [[Property u]]Source
Group properties into blocks delimited by begin..end
pairs.
Value Parsers
pa_URI :: ValueParser uSource
pa_text :: ValueParser uSource
Unescape slashes, newlines and commas.
pa_date :: ValueParser uSource
pa_time :: ValueParser uSource
Value parser combinators
many :: ValueParser u -> ValueParser uSource
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
printDirectory :: PrintValue u => Directory u -> ByteStringSource
printDirectory' :: PrintValue u => [Property u] -> ByteStringSource
printProperty :: PrintValue u => Property u -> ByteStringSource