property-list-0.1.0.1: XML property list parser

Data.PropertyList

Contents

Synopsis

The basic property list types

Property lists have several supported representations, but the main one most end users will care about is PropertyList. This is a basic algebraic representation of property lists which can be constructed using the polymorphic constructors described below and pattern-matched using the polymorphic destructors (designed for convenient usage with the ViewPatterns extension)

Also provided is the PartialPropertyList representation, which is a property list that is extended by adding a new constructor containing some arbitrary type chosen by the user. It is mostly used as an intermediate represenation for property lists that have been parsed into their overall shape but not all elements have been parsed into their final format.

The UnparsedXmlPlistItem and UnparsedBPListRecord types are used with PartialPropertyList, and that is really their only purpose - to represent unparseable items during intermediate stages of translation.

data UnparsedXmlPlistItem Source

A representation of values that were structurally sound in the property list file but the contents of which couldn't be interpreted as what they claimed to be. The result of the initial parse phase will typically be a PartialPropertyList UnparsedXmlPlistItem, and if the whole plist was parsed properly will contain no actual values of this type.

Constructors and destructors for property lists

The "pl*" operations construct PropertyLists, PartialPropertyLists, or any other types defining an unlifted algebra for the PropertyListS signature.

The "fromPl*" operations are ViewPattern matching operations for PropertyList, PartialPropertyList, or any other type defining a Maybe-lifted coalgebra for PropertyListS.

The generality of these operations means that they can also be used to directly generate or analyze "external" formats such as the XML Plist representation.

The internal algebraic model for property lists

Internally, conversions between various property list representations are all defined in terms of universal algebra, which is basically just fancy math-talk for "very general interfaces that let you convert between certain kinds of representations easily and efficiently".

Most users do not need to understand this stuff - the class names are only exported because they appear in the types of the constructors and destructors. For more detailed info, see Data.PropertyList.Algebra.

class Functor f => PListAlgebra f a Source

A class for types which can be constructed algebraically from the PropertyListS signature (lifted by f) - in other words, types which you can put property lists into.

The f-lifting is provided to support extending the algebra. The algebra is defined in a class rather than passing around functions because most of the time for any given type there is only one algebra you care about.

Typically a renderer for an output format will be implemented as a type with an instance PListAlgebra Identity. For example, the XML output system is implemented in the instance PListAlgebra Identity Data.PropertyList.Xml.Types.Plist.

class Functor f => PListCoalgebra f a Source

A class for types which can be dissected (pattern-matched) into the PropertyListS signature (lifted by f) - in other words, types which you can take property lists out of.

Typically a property list parser will be implemented as a type with a PListCoalgebra instance, where f is either Identity in the case where the parser guarantees to return a fully well-formed property list (assuming it returns anything at all) or Either something when the parser only guarantees that the structure is sound (but that some elements might be defective, in which case a value of type something would be substituted). The XML parser, for example, is based on the latter approach, where something is UnparsedPlistItem.

class (PListAlgebra f a, PListCoalgebra f a) => InitialPList f a | f -> a, a -> fSource

An identification of the fact that the type a has an initial plist algebra (under some lifting f). Functional dependencies are in use - for any type, only one of its initial algebras (if multiple apply, which they may because the same type may be initial for multiple distinct liftings) can be chosen, and for any lifting only one type's algebra may be chosen. This is to make types decidable in the not-so-uncommon case where the lifting is encapsulated (eg, any time foldPList is partially applied - for example, see the signature of fromPlist).

For cases where the lifting either needs to be chosen or needs to be transformed to another lifting, fromPlistWith is provided. It is based on the same definition as the default implementation of foldPList but also inserts a chosen transformation of the lifting.

Question for self: Is the PListCoalgebra context reasonable here? Some rough calculations suggest that in the presence of fixed point type operators, it is possible to construct a PListCoalgebra for any InitialPList, which essentially is defined as pattern matching. So, I'm not totally sure but I think this is reasonable - at least, for finitary signatures, which we're using as long as f doesn't go crazy.

class (PListCoalgebra f a, PListAlgebra f a) => TerminalPList f a | f -> a, a -> fSource

Chosen terminal coalgebra for the given lifting, and chosen lifting for the given type. See also InitialPList.

Parsing and formatting property lists using any supported format

readPropertyListFromFile :: FilePath -> IO PropertyListSource

Read a property list from a file, trying all supported property list formats. Presently, the "XML1" and "bplist00" formats are supported. See also readXmlPropertyListFromFile and readBinaryPropertyListFromFile.

writePropertyListToFile :: FilePath -> PropertyList -> IO ()Source

Write a property list to a file, using a "preferred" property list format. Presently, that is the "XML1" format. See also writeXmlPropertyListToFile.

Parsing and formatting property lists using the Binary format

Parsing and formatting property lists using the XML format

readXmlPropertyList :: String -> Either String PropertyListSource

Read a property list from a String in the xml1 format. If parsing fails, returns a description of the problem in the Left result.

showXmlPropertyList :: (InitialPList f pl, PListAlgebra f Element) => pl -> StringSource

Render a propertylist to a String in the xml1 plist format from any initial propertylist type (which includes PropertyList, PartialPropertyList UnparsedPlistItem, and PartialPropertyList PlistItem).

readXmlPropertyListFromFile :: FilePath -> IO PropertyListSource

Read a property list from a file in the xml1 format. If parsing fails, calls fail.

writeXmlPropertyListToFile :: FilePath -> PropertyList -> IO ()Source

Output a propertylist to a file in the xml1 plist format from any initial propertylist type (which includes PropertyList, PartialPropertyList UnparsedPlistItem, and PartialPropertyList PlistItem).

Manipulating property lists

This module exports a class (PropertyListItem) and several functions used to manipulate PropertyLists and their contents at a high level, viewing and manipulating the data in the tree through ad-hoc transformations.

For example, consider the following property list:

 myPlist = plDict $ M.fromList
    [ ("foo", plInt 4)
    , ("bar", plString "qux")
    , ("subDict", plDict $ M.fromList
         [ ("item 1", plString "This is item 1!")
         , ("item B", plBool True)
         ])
    ] :: PropertyList

Some typical actions you might do with a plist like this (Note that in many cases a Just is added - this is because the key-path operations are defined in terms of Maybe so that operations like setItemAtKeyPath or alterItemAtKeyPath can create new items where none already exist):

 getItemAtKeyPath ["subDict", "item B"] (Just myPlist) :: Maybe Bool

(returns Just True)

 getItemAtKeyPath ["subDict"] (Just myPlist) :: Maybe (M.Map String String)

(returns Just (M.fromList [("item 1", "This is item 1!"), ("item B", "YES")]). Note the stringification of non-string items. In general, PropertyListItem instances are expected to do "reasonable" conversions to try and make sense of what the user is asking the system to do.)

 setItemAtKeyPath ["omg", "lolwut"] (Just "roflcopter") (Just myPlist)

(returns a modified version of myPlist with plDict $ M.fromList [("omg", plDict $ M.fromList [("lolwut", plString "roflcopter")])] added to the root dictionary)

 setItemAtKeyPath ["foo"] Nothing (Just myPlist)

(returns a modified version of myPlist with the "foo" entry in the root dictionary deleted)

 setItemAtKeyPath ["foo", "bar", "baz"] (Just "qux") Nothing

(returns a new dictionary with plString "qux" at the key path foo.bar.baz)

class PropertyListItem i whereSource

A class for items which can be converted to and from property lists. This is more general than PListAlgebra and PListCoalgebra, in that it allows for transformations that are not primitive-recursive. This relaxation is necessary and desirable in the PropertyListItem situation because we are more interested in composable injection/projection operations on than in universal maps.

The algebraic interface also cannot work for arrays or dictionaries, because it only allows primitive (co-)recursion - the conversions can only operate on one "layer" of PropertyListS at a time. This could be handled by enlarging the types (from [t] to Either t [t], for example) or by encoding in-band (by taking a singleton list to be an element instead of a list, for example), but both of those "solutions" create headaches of their own, and in any case the algebraic interface is probably too bizarre for most users.

Methods

toPropertyList :: i -> PropertyListSource

Construct a PropertyList from the item.

fromPropertyList :: PropertyList -> Maybe iSource

Convert a property list to a property list item if its contents _exactly_ fit the target type. Note that when using types such as Map String Int (as opposed to Map String PropertyList) this will mean that a single element of the dictionary of a non-Int type will cause the entire conversion to fail.

listToPropertyList :: [i] -> PropertyListSource

In order to support a general instance for lists without breaking String, we use the same trick as the Prelude uses for Show. Generally, the list methods should not be overridden, and maybe they shouldn't even be exported.

listFromPropertyList :: PropertyList -> Maybe [i]Source

Instances

PropertyListItem Bool 
PropertyListItem Char 
PropertyListItem Double 
PropertyListItem Float 
PropertyListItem Int 
PropertyListItem Int8 
PropertyListItem Int16 
PropertyListItem Int32 
PropertyListItem Int64 
PropertyListItem Integer 
PropertyListItem Word8 
PropertyListItem Word16 
PropertyListItem Word32 
PropertyListItem Word64 
PropertyListItem ByteString 
PropertyListItem ByteString 
PropertyListItem Text 
PropertyListItem UTCTime 
PropertyListItem PropertyList 
PropertyListItem a => PropertyListItem [a] 
(PropertyListItem a1, PropertyListItem a2) => PropertyListItem (Either a1 a2) 
PropertyListItem a => PropertyListItem (Map String a) 
(PropertyListItem a1, PropertyListItem a2) => PropertyListItem (OneOf2 a1 a2) 
(PropertyListItem a1, PropertyListItem a2, PropertyListItem a3) => PropertyListItem (OneOf3 a1 a2 a3) 
(PropertyListItem a1, PropertyListItem a2, PropertyListItem a3, PropertyListItem a4) => PropertyListItem (OneOf4 a1 a2 a3 a4) 
(PropertyListItem a1, PropertyListItem a2, PropertyListItem a3, PropertyListItem a4, PropertyListItem a5) => PropertyListItem (OneOf5 a1 a2 a3 a4 a5) 
(PropertyListItem a1, PropertyListItem a2, PropertyListItem a3, PropertyListItem a4, PropertyListItem a5, PropertyListItem a6) => PropertyListItem (OneOf6 a1 a2 a3 a4 a5 a6) 
(PropertyListItem a1, PropertyListItem a2, PropertyListItem a3, PropertyListItem a4, PropertyListItem a5, PropertyListItem a6, PropertyListItem a7) => PropertyListItem (OneOf7 a1 a2 a3 a4 a5 a6 a7) 
(PropertyListItem a1, PropertyListItem a2, PropertyListItem a3, PropertyListItem a4, PropertyListItem a5, PropertyListItem a6, PropertyListItem a7, PropertyListItem a8) => PropertyListItem (OneOf8 a1 a2 a3 a4 a5 a6 a7 a8) 
(PropertyListItem a1, PropertyListItem a2, PropertyListItem a3, PropertyListItem a4, PropertyListItem a5, PropertyListItem a6, PropertyListItem a7, PropertyListItem a8, PropertyListItem a9) => PropertyListItem (OneOf9 a1 a2 a3 a4 a5 a6 a7 a8 a9) 
(PropertyListItem a1, PropertyListItem a2, PropertyListItem a3, PropertyListItem a4, PropertyListItem a5, PropertyListItem a6, PropertyListItem a7, PropertyListItem a8, PropertyListItem a9, PropertyListItem a10) => PropertyListItem (OneOf10 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10) 
(PropertyListItem a1, PropertyListItem a2, PropertyListItem a3, PropertyListItem a4, PropertyListItem a5, PropertyListItem a6, PropertyListItem a7, PropertyListItem a8, PropertyListItem a9, PropertyListItem a10, PropertyListItem a11) => PropertyListItem (OneOf11 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11) 
(PropertyListItem a1, PropertyListItem a2, PropertyListItem a3, PropertyListItem a4, PropertyListItem a5, PropertyListItem a6, PropertyListItem a7, PropertyListItem a8, PropertyListItem a9, PropertyListItem a10, PropertyListItem a11, PropertyListItem a12) => PropertyListItem (OneOf12 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12) 
(PropertyListItem a1, PropertyListItem a2, PropertyListItem a3, PropertyListItem a4, PropertyListItem a5, PropertyListItem a6, PropertyListItem a7, PropertyListItem a8, PropertyListItem a9, PropertyListItem a10, PropertyListItem a11, PropertyListItem a12, PropertyListItem a13) => PropertyListItem (OneOf13 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13) 
(PropertyListItem a1, PropertyListItem a2, PropertyListItem a3, PropertyListItem a4, PropertyListItem a5, PropertyListItem a6, PropertyListItem a7, PropertyListItem a8, PropertyListItem a9, PropertyListItem a10, PropertyListItem a11, PropertyListItem a12, PropertyListItem a13, PropertyListItem a14) => PropertyListItem (OneOf14 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) 
(PropertyListItem a1, PropertyListItem a2, PropertyListItem a3, PropertyListItem a4, PropertyListItem a5, PropertyListItem a6, PropertyListItem a7, PropertyListItem a8, PropertyListItem a9, PropertyListItem a10, PropertyListItem a11, PropertyListItem a12, PropertyListItem a13, PropertyListItem a14, PropertyListItem a15) => PropertyListItem (OneOf15 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14 a15) 
(PropertyListItem a1, PropertyListItem a2, PropertyListItem a3, PropertyListItem a4, PropertyListItem a5, PropertyListItem a6, PropertyListItem a7, PropertyListItem a8, PropertyListItem a9, PropertyListItem a10, PropertyListItem a11, PropertyListItem a12, PropertyListItem a13, PropertyListItem a14, PropertyListItem a15, PropertyListItem a16) => PropertyListItem (OneOf16 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14 a15 a16) 
(PropertyListItem a1, PropertyListItem a2, PropertyListItem a3, PropertyListItem a4, PropertyListItem a5, PropertyListItem a6, PropertyListItem a7, PropertyListItem a8, PropertyListItem a9, PropertyListItem a10, PropertyListItem a11, PropertyListItem a12, PropertyListItem a13, PropertyListItem a14, PropertyListItem a15, PropertyListItem a16, PropertyListItem a17) => PropertyListItem (OneOf17 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14 a15 a16 a17) 
(PropertyListItem a1, PropertyListItem a2, PropertyListItem a3, PropertyListItem a4, PropertyListItem a5, PropertyListItem a6, PropertyListItem a7, PropertyListItem a8, PropertyListItem a9, PropertyListItem a10, PropertyListItem a11, PropertyListItem a12, PropertyListItem a13, PropertyListItem a14, PropertyListItem a15, PropertyListItem a16, PropertyListItem a17, PropertyListItem a18) => PropertyListItem (OneOf18 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14 a15 a16 a17 a18) 
(PropertyListItem a1, PropertyListItem a2, PropertyListItem a3, PropertyListItem a4, PropertyListItem a5, PropertyListItem a6, PropertyListItem a7, PropertyListItem a8, PropertyListItem a9, PropertyListItem a10, PropertyListItem a11, PropertyListItem a12, PropertyListItem a13, PropertyListItem a14, PropertyListItem a15, PropertyListItem a16, PropertyListItem a17, PropertyListItem a18, PropertyListItem a19) => PropertyListItem (OneOf19 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14 a15 a16 a17 a18 a19) 
(PropertyListItem a1, PropertyListItem a2, PropertyListItem a3, PropertyListItem a4, PropertyListItem a5, PropertyListItem a6, PropertyListItem a7, PropertyListItem a8, PropertyListItem a9, PropertyListItem a10, PropertyListItem a11, PropertyListItem a12, PropertyListItem a13, PropertyListItem a14, PropertyListItem a15, PropertyListItem a16, PropertyListItem a17, PropertyListItem a18, PropertyListItem a19, PropertyListItem a20) => PropertyListItem (OneOf20 a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14 a15 a16 a17 a18 a19 a20) 

alterItemAtKeyPathM :: (Monad m, PropertyListItem i, PropertyListItem i') => [String] -> (Maybe i -> m (Maybe i')) -> Maybe PropertyList -> m (Maybe PropertyList)Source

alterItemAtKeyPathM path f applies the function f deep inside the PropertyList on the property list item at the given key-path path (if possible). This is the same notion of key path as is used in the Apple plist APIs - each component of the path indicates descending into a dictionary by selecting the element with that key (if any). If a key is not found, it is created. If a key is found but is not a dictionary, the operation fails (with fail from the Monad class).

If the result of f is Nothing, and the resulting dictionary is empty, that dictionary is deleted in the result (and any empty parent dictionaries). If this is not the behavior you want, you should alter the parent dictionary itself and return an empty one.

alterItemAtKeyPath :: (PropertyListItem i, PropertyListItem i') => [String] -> (Maybe i -> Maybe i') -> Maybe PropertyList -> Maybe PropertyListSource

alterItemAtKeyPath path f applies the function f deep inside the PropertyList on the property list item at the given key-path path (if possible). This is the same notion of key path as is used in the Apple plist APIs - namely, each component of the path indicates descending into a dictionary by selecting the element with that key (if any). If a key is not found, it is created. If a key is found but is not a dictionary, the operation fails (with error).

If the result of f is Nothing, and the resulting dictionary is empty, that dictionary is deleted in the result (and any empty parent dictionaries). If this is not the behavior you want, you should alter the parent dictionary itself and return an empty one.

getItemAtKeyPath :: PropertyListItem i => [String] -> Maybe PropertyList -> Maybe iSource

Gets the item, if any (and if convertible to the required type), at a given key path. If the key path passes through something that is not a dictionary, the operation returns Nothing.

setItemAtKeyPath :: PropertyListItem i => [String] -> Maybe i -> Maybe PropertyList -> Maybe PropertyListSource

Sets the item at a given key-path. If the key path does not exist, it is created. If it exists but passes through something that is not a dictionary, the operation fails (with error)