Safe Haskell | None |
---|
The internal "algebraic" interface for working with property-list-like things. The classes defined here are the basis for a very general system supporting transformations between many property-list representations, including both internal and external formats. The transformations are based on algebra and are very well-behaved mathematically. It is possible to "fuse" operations so that, for example, reading from XML and writing to a text plist can be done without creating any intermediate representations other than those used by the XML parser and the text renderer. Or, expressions using the "smart constructors" can be evaluated to directly synthesize XML-formatted plists, or the view-pattern destructors can be used to directly analyze them.
The interface defined in this module is very heavily influenced by
category-theoretical constructions. In particular, F-algebras and
F-coalgebras, initiality, and terminality. For those not familiar with
these concepts, this will probably be quite incomprehensible. Sorry
about that. The basic idea, though, is the use of the PropertyListS
type as a sort of a central junction point through which all conversions
between property-list-like types and property-list-item types are routed.
The classes defined here are chosen to minimize the inderdependence of
these types and hence maximize the flexibility of the system as a whole.
More simply stated, these weird math thingies make the design as flexible as possible (in a well-defined and useful sense).
- data PropertyListS a
- foldPropertyListS :: ([a] -> t) -> (ByteString -> t) -> (UTCTime -> t) -> (Map String a -> t) -> (Double -> t) -> (Integer -> t) -> (String -> t) -> (Bool -> t) -> PropertyListS a -> t
- class Functor f => PListAlgebra f a where
- plistAlgebra :: f (PropertyListS a) -> a
- class (PListAlgebra f a, PListCoalgebra f a) => InitialPList f a | f -> a, a -> f where
- foldPList :: (f (PropertyListS t) -> t) -> a -> t
- fromPlist :: (InitialPList f pl, PListAlgebra f t) => pl -> t
- fromPlistWith :: (PListCoalgebra f pl, PListAlgebra g t) => (f (PropertyListS t) -> g (PropertyListS t)) -> pl -> t
- class Functor f => PListCoalgebra f a where
- plistCoalgebra :: a -> f (PropertyListS a)
- class (PListCoalgebra f a, PListAlgebra f a) => TerminalPList f a | f -> a, a -> f where
- unfoldPList :: (t -> f (PropertyListS t)) -> t -> a
- toPlist :: (PListCoalgebra f t, TerminalPList f pl) => t -> pl
- toPlistWith :: (PListCoalgebra f t, PListAlgebra g pl) => (f (PropertyListS t) -> g (PropertyListS t)) -> t -> pl
- plArray :: PListAlgebra Identity a => [a] -> a
- plData :: PListAlgebra Identity a => ByteString -> a
- plDate :: PListAlgebra Identity a => UTCTime -> a
- plDict :: PListAlgebra Identity a => Map String a -> a
- plReal :: PListAlgebra Identity a => Double -> a
- plInt :: PListAlgebra Identity a => Integer -> a
- plString :: PListAlgebra Identity a => String -> a
- plBool :: PListAlgebra Identity a => Bool -> a
- fromPlArray :: PListCoalgebra Maybe a => a -> Maybe [a]
- fromPlData :: PListCoalgebra Maybe a => a -> Maybe ByteString
- fromPlDate :: PListCoalgebra Maybe a => a -> Maybe UTCTime
- fromPlDict :: PListCoalgebra Maybe a => a -> Maybe (Map String a)
- fromPlReal :: PListCoalgebra Maybe a => a -> Maybe Double
- fromPlInt :: PListCoalgebra Maybe a => a -> Maybe Integer
- fromPlString :: PListCoalgebra Maybe a => a -> Maybe String
- fromPlBool :: PListCoalgebra Maybe a => a -> Maybe Bool
The signature type (PropertyListS
)
data PropertyListS a Source
The signature of the base property list algebra. This algebra is
"lifted" in various ways to support several different but similar
representations of property lists as well as projections and
injections. All the different representations are connected
through
this signature.
For example, PropertyList
is a fixed-point of this signature - that
is, a recursive version where a
is instantiated as
.
That gives the "expected" structure of a basic property list. It is both
initial and terminal for this signature in its 'un-lifted' form - which
is to say, any other type with an algebra for this signature (such as an
XML representation) can be made from a PropertyListS
aPropertyList
, and any type with
a coalgebra for this signature (such as a String
, an Integer
, etc.)
can be converted directly to a PropertyList
. This also means that any
transformation or series of transformations involving the PropertyList
type can be fused to "skip" generating intermediate property lists,
although there are currently no rewrite rules set up to do so.
Similarly, PartialPropertyList
is a fixed point of an arbitrarily-
augmented version of this signature (also known as the free monad
generated by the signature). Depending on its type parameter,
PartialPropertyList
can be terminal among many simple extensions to
the signature. Thus many types with a coalgebra for an extension of
this signature (such as XML given an appropriate tree destructor, or
the PropertyList
type itself) can be trivially converted to a
PartialPropertyList
.
PLArray [a] | |
PLData ByteString | |
PLDate UTCTime | |
PLDict (Map String a) | |
PLReal Double | |
PLInt Integer | |
PLString String | |
PLBool Bool |
Functor PropertyListS | |
Foldable PropertyListS | |
Traversable PropertyListS | |
Eq a => Eq (PropertyListS a) | |
Ord a => Ord (PropertyListS a) | |
Read a => Read (PropertyListS a) | |
Show a => Show (PropertyListS a) |
foldPropertyListS :: ([a] -> t) -> (ByteString -> t) -> (UTCTime -> t) -> (Map String a -> t) -> (Double -> t) -> (Integer -> t) -> (String -> t) -> (Bool -> t) -> PropertyListS a -> tSource
Construct a basic non-recursive algebra of property list items.
This is equivalent to pattern matching on PropertyListS
.
The algebra and coalgebra classes
class Functor f => PListAlgebra f a whereSource
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
. For example, the XML
output system is implemented in the PListAlgebra
Identity
instance
.
PListAlgebra
Identity
Plist
plistAlgebra :: f (PropertyListS a) -> aSource
Build a value of type a
from a piece of a property list (using
the PropertyListS
signature augmented by the "lifting" f
).
class (PListAlgebra f a, PListCoalgebra f a) => InitialPList f a | f -> a, a -> f whereSource
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.
foldPList :: (f (PropertyListS t) -> t) -> a -> tSource
Using some other plist algebra, compute the unique transformation from
the type a
to that algebra.
The default implementation is:
foldPList f = go where go = f . fmap (fmap go) . plistCoalgebra
fromPlist :: (InitialPList f pl, PListAlgebra f t) => pl -> tSource
Convert from an initial plist to any other plist with the same lifted algebra.
fromPlistWith :: (PListCoalgebra f pl, PListAlgebra g t) => (f (PropertyListS t) -> g (PropertyListS t)) -> pl -> tSource
class Functor f => PListCoalgebra f a whereSource
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
.
plistCoalgebra :: a -> f (PropertyListS a)Source
Analyze a value of type a
by matching it to a constructor in the
(lifted by f
) PropertyListS
signature.
class (PListCoalgebra f a, PListAlgebra f a) => TerminalPList f a | f -> a, a -> f whereSource
Chosen terminal coalgebra for the given lifting, and chosen lifting
for the given type. See also InitialPList
.
unfoldPList :: (t -> f (PropertyListS t)) -> t -> aSource
Given some coalgebra for the chosen lifted plist signature, compute
the unique extraction/unfolding of that coalgebra into the type a
.
The default implementation is:
unfoldPList f = go where go = plistAlgebra . fmap (fmap go) . f
toPlist :: (PListCoalgebra f t, TerminalPList f pl) => t -> plSource
Convert from any plist-like thing to a plist which is terminal for a some lifted algebra.
toPlistWith :: (PListCoalgebra f t, PListAlgebra g pl) => (f (PropertyListS t) -> g (PropertyListS t)) -> t -> plSource
"Smart" constructors for any PListAlgebra
.
plArray :: PListAlgebra Identity a => [a] -> aSource
plData :: PListAlgebra Identity a => ByteString -> aSource
plDate :: PListAlgebra Identity a => UTCTime -> aSource
plReal :: PListAlgebra Identity a => Double -> aSource
plInt :: PListAlgebra Identity a => Integer -> aSource
plString :: PListAlgebra Identity a => String -> aSource
plBool :: PListAlgebra Identity a => Bool -> aSource
"View pattern" destructors for any PListCoalgebra
.
fromPlArray :: PListCoalgebra Maybe a => a -> Maybe [a]Source
fromPlData :: PListCoalgebra Maybe a => a -> Maybe ByteStringSource
fromPlDate :: PListCoalgebra Maybe a => a -> Maybe UTCTimeSource
fromPlDict :: PListCoalgebra Maybe a => a -> Maybe (Map String a)Source
fromPlReal :: PListCoalgebra Maybe a => a -> Maybe DoubleSource
fromPlString :: PListCoalgebra Maybe a => a -> Maybe StringSource
fromPlBool :: PListCoalgebra Maybe a => a -> Maybe BoolSource