Copyright | (C) 2020 Sophie Taylor |
---|---|
License | AGPL-3.0-or-later |
Maintainer | Sophie Taylor <sophie@spacekitteh.moe> |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | GHC2021 |
Games.ECS.Serialisation
Description
Generic XML serialisation and deserialisation support. Adapted from the generic-xmlpickler library, based on the hxt package.
Synopsis
- class XMLSerialise a where
- serialise :: String -> a -> Element
- deserialise :: String -> Element -> Either UnpickleError a
- class XMLPickler t a where
- class XMLPickleAsAttribute a where
- pickleAsAttribute :: Name -> PU [Attribute] a
- data Node
- module Data.XML.Pickle
- newtype AsString a = AsString {
- unAsString :: a
- class GXmlPickler t (f :: Type -> Type) where
- formatElement :: String -> String
- newtype AsList a = AsList {
- unAsList :: a
- optElem :: forall t i (s :: Meta) (f :: Type -> Type) p a. Selector s => PU [Node] a -> t i s f p -> PU [Node] a
- optElemD :: forall t i (s :: Meta) (f :: Type -> Type) p a. Datatype s => PU [Node] a -> t i s f p -> PU [Node] a
- optElemC :: forall t i (s :: Meta) (f :: Type -> Type) p a. Constructor s => PU [Node] a -> t i s f p -> PU [Node] a
Documentation
class XMLSerialise a where Source #
A convenience wrapper around an XMLPickler
.
Minimal complete definition
Nothing
Methods
serialise :: String -> a -> Element Source #
Serialise an a as a named Element
.
deserialise :: String -> Element -> Either UnpickleError a Source #
Deserialise a named Element
.
default deserialise :: XMLPickler [Node] a => String -> Element -> Either UnpickleError a Source #
Instances
XMLPickler [Node] a => XMLSerialise a Source # | |
Defined in Games.ECS.Serialisation |
class XMLPickler t a where Source #
A lower-level pickler class.
Minimal complete definition
Nothing
Methods
A combined pickler/unpickler.
Instances
class XMLPickleAsAttribute a where Source #
For when a type can be pickled as an XML Attribute
.
Instances
XMLPickleAsAttribute InternedText Source # | |
Defined in Games.ECS.Serialisation Methods pickleAsAttribute :: Name -> PU [Attribute] InternedText Source # | |
XMLPickleAsAttribute Entity Source # | |
Defined in Games.ECS.Entity | |
XMLPickleAsAttribute PrototypeID Source # | |
Defined in Games.ECS.Prototype.PrototypeID Methods pickleAsAttribute :: Name -> PU [Attribute] PrototypeID Source # | |
(Read a, Show a) => XMLPickleAsAttribute a Source # | |
Defined in Games.ECS.Serialisation | |
(IsString a, Show a) => XMLPickleAsAttribute (AsString a) Source # | |
Defined in Games.ECS.Serialisation | |
XMLPickleAsAttribute a => XMLPickleAsAttribute (Maybe a) Source # | |
Defined in Games.ECS.Serialisation |
Instances
module Data.XML.Pickle
A deriving-via helper.
Constructors
AsString | |
Fields
|
Instances
IsString a => IsString (AsString a) Source # | |
Defined in Games.ECS.Serialisation Methods fromString :: String -> AsString a # | |
Read a => Read (AsString a) Source # | |
Show a => Show (AsString a) Source # | |
Eq a => Eq (AsString a) Source # | |
(IsString a, Show a) => XMLPickleAsAttribute (AsString a) Source # | |
Defined in Games.ECS.Serialisation | |
(Read a, Show a) => XMLPickler [Node] (AsString a) Source # | |
class GXmlPickler t (f :: Type -> Type) where Source #
Generic pickling support.
Minimal complete definition
Instances
(GXmlPickler t f, GXmlPickler t g) => GXmlPickler t (f :+: g) Source # | For sums of constructors |
XMLPickler t a => GXmlPickler t (K1 i a :: Type -> Type) Source # | For individual fields |
(Datatype d, GXmlPickler t f) => GXmlPickler t (M1 D d f) Source # | For datatypes |
GXmlPickler [t] (U1 :: Type -> Type) Source # | For empty constructors |
(GXmlPickler [t] f, GXmlPickler [t] g) => GXmlPickler [t] (f :*: g) Source # | For products of fields |
(Constructor c, GXmlPickler [Node] f) => GXmlPickler [Node] (M1 C c f) Source # | For constructors |
(Constructor c'', ty ~ M1 C c'' (M1 S c (K1 i Entity :: k -> Type))) => GXmlPickler [Node] (M1 C c'' (M1 S c (K1 i Entity :: Type -> Type))) Source # | An instance for constructors which only contain an entity reference; we put that as an attribute. |
(KnownSymbol name, XMLPickler [Node] a, Datatype d, ty ~ M1 D d (M1 C c'' (M1 S c (K1 i a :: k -> Type)))) => GXmlPickler [Node] (M1 D d (M1 C c'' (M1 S c (K1 i (TaggedComponent name (Maybe a)) :: Type -> Type)))) Source # | An instance for wrapper components. Don't bother with the wrapper constructor or fieldname; just the wrapped data. |
Defined in Games.ECS.Component | |
(XMLPickler [Node] a, Selector c) => GXmlPickler [Node] (M1 S c (K1 i (Maybe a) :: Type -> Type)) Source # | For Maybe types |
(Selector c, GXmlPickler [Node] f) => GXmlPickler [Node] (M1 S c f) Source # | For record field selectors |
formatElement :: String -> String Source #
Format field names nicely
A deriving-via helper.
optElem :: forall t i (s :: Meta) (f :: Type -> Type) p a. Selector s => PU [Node] a -> t i s f p -> PU [Node] a Source #
Pickle adapter for Selector