ohhecs-0.0.2: An Entity-Component-Systems engine core.
Copyright(C) 2020 Sophie Taylor
LicenseAGPL-3.0-or-later
MaintainerSophie Taylor <sophie@spacekitteh.moe>
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageGHC2021

Games.ECS.Serialisation

Description

Generic XML serialisation and deserialisation support. Adapted from the generic-xmlpickler library, based on the hxt package.

Synopsis

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.

default serialise :: XMLPickler [Node] a => String -> a -> Element Source #

deserialise :: String -> Element -> Either UnpickleError a Source #

Deserialise a named Element.

Instances

Instances details
XMLPickler [Node] a => XMLSerialise a Source # 
Instance details

Defined in Games.ECS.Serialisation

class XMLPickler t a where Source #

A lower-level pickler class.

Minimal complete definition

Nothing

Methods

xpickle :: PU t a Source #

A combined pickler/unpickler.

default xpickle :: (Generic a, GXmlPickler t (Rep a)) => PU t a Source #

Instances

Instances details
(Read a, Show a) => XMLPickler Text a Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU Text a Source #

(Generic a, GXmlPickler t (Rep a)) => XMLPickler t a Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU t a Source #

XMLPickler [Node] Int16 Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] Int16 Source #

XMLPickler [Node] Int32 Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] Int32 Source #

XMLPickler [Node] Int64 Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] Int64 Source #

XMLPickler [Node] Int8 Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] Int8 Source #

XMLPickler [Node] Word16 Source # 
Instance details

Defined in Games.ECS.Serialisation

XMLPickler [Node] Word32 Source # 
Instance details

Defined in Games.ECS.Serialisation

XMLPickler [Node] Word64 Source # 
Instance details

Defined in Games.ECS.Serialisation

XMLPickler [Node] Word8 Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] Word8 Source #

XMLPickler [Node] InternedText Source # 
Instance details

Defined in Games.ECS.Serialisation

XMLPickler [Node] Entity Source # 
Instance details

Defined in Games.ECS.Entity

XMLPickler [Node] IsPrototype Source # 
Instance details

Defined in Games.ECS.Prototype

XMLPickler [Node] PrototypeID Source # 
Instance details

Defined in Games.ECS.Prototype.PrototypeID

XMLPickler [Node] SpawnedFromPrototype Source # 
Instance details

Defined in Games.ECS.Prototype.SpawnedFromPrototype

XMLPickler [Node] Text Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] Text Source #

XMLPickler [Node] String Source # 
Instance details

Defined in Games.ECS.Serialisation

XMLPickler [Node] Integer Source # 
Instance details

Defined in Games.ECS.Serialisation

XMLPickler [Node] Natural Source # 
Instance details

Defined in Games.ECS.Serialisation

XMLPickler [Node] Bool Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] Bool Source #

XMLPickler [Node] Char Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] Char Source #

XMLPickler [Node] Double Source # 
Instance details

Defined in Games.ECS.Serialisation

XMLPickler [Node] Float Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] Float Source #

XMLPickler [Node] Int Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] Int Source #

XMLPickler [Node] Word Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] Word Source #

XMLPickler [Node] v => XMLPickler [Node] (Seq v) Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] (Seq v) Source #

(IsList a, XMLPickler [Node] (Item a)) => XMLPickler [Node] (AsList a) Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] (AsList a) Source #

(Read a, Show a) => XMLPickler [Node] (AsString a) Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] (AsString a) Source #

(Ord a, XMLPickler [Node] a) => XMLPickler [Node] (OSet a) Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] (OSet a) Source #

(Eq v, Hashable v, XMLPickler [Node] v) => XMLPickler [Node] (HashSet v) Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] (HashSet v) Source #

XMLPickler [Node] v => XMLPickler [Node] (HashMap Entity v) Source # 
Instance details

Defined in Games.ECS.Entity

Methods

xpickle :: PU [Node] (HashMap Entity v) Source #

(Eq k, Hashable k, XMLPickleAsAttribute k, XMLPickler [Node] v) => XMLPickler [Node] (HashMap k v) Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] (HashMap k v) Source #

(Eq a, KnownSymbol name, KnownSymbol (AppendSymbol name "TaggedComponent wrapper"), XMLPickler [Node] a) => XMLPickler [Node] (TaggedComponent name (Maybe a)) Source # 
Instance details

Defined in Games.ECS.Component

Methods

xpickle :: PU [Node] (TaggedComponent name (Maybe a)) Source #

(KnownSymbol name, KnownSymbol (AppendSymbol name "TaggedComponent wrapper"), XMLPickler [Node] a) => XMLPickler [Node] (TaggedComponent name a) Source # 
Instance details

Defined in Games.ECS.Component

Methods

xpickle :: PU [Node] (TaggedComponent name a) Source #

data Node #

Instances

Instances details
Data Node 
Instance details

Defined in Data.XML.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Node -> c Node #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Node #

toConstr :: Node -> Constr #

dataTypeOf :: Node -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Node) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Node) #

gmapT :: (forall b. Data b => b -> b) -> Node -> Node #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Node -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Node -> r #

gmapQ :: (forall d. Data d => d -> u) -> Node -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Node -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Node -> m Node #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Node -> m Node #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Node -> m Node #

IsString Node 
Instance details

Defined in Data.XML.Types

Methods

fromString :: String -> Node #

Generic Node 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep Node 
Instance details

Defined in Data.XML.Types

Methods

from :: Node -> Rep Node x #

to :: Rep Node x -> Node #

Show Node 
Instance details

Defined in Data.XML.Types

Methods

showsPrec :: Int -> Node -> ShowS #

show :: Node -> String #

showList :: [Node] -> ShowS #

NFData Node 
Instance details

Defined in Data.XML.Types

Methods

rnf :: Node -> () #

Eq Node 
Instance details

Defined in Data.XML.Types

Methods

(==) :: Node -> Node -> Bool #

(/=) :: Node -> Node -> Bool #

Ord Node 
Instance details

Defined in Data.XML.Types

Methods

compare :: Node -> Node -> Ordering #

(<) :: Node -> Node -> Bool #

(<=) :: Node -> Node -> Bool #

(>) :: Node -> Node -> Bool #

(>=) :: Node -> Node -> Bool #

max :: Node -> Node -> Node #

min :: Node -> Node -> Node #

XMLPickler [Node] Int16 Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] Int16 Source #

XMLPickler [Node] Int32 Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] Int32 Source #

XMLPickler [Node] Int64 Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] Int64 Source #

XMLPickler [Node] Int8 Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] Int8 Source #

XMLPickler [Node] Word16 Source # 
Instance details

Defined in Games.ECS.Serialisation

XMLPickler [Node] Word32 Source # 
Instance details

Defined in Games.ECS.Serialisation

XMLPickler [Node] Word64 Source # 
Instance details

Defined in Games.ECS.Serialisation

XMLPickler [Node] Word8 Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] Word8 Source #

XMLPickler [Node] InternedText Source # 
Instance details

Defined in Games.ECS.Serialisation

XMLPickler [Node] Entity Source # 
Instance details

Defined in Games.ECS.Entity

XMLPickler [Node] IsPrototype Source # 
Instance details

Defined in Games.ECS.Prototype

XMLPickler [Node] PrototypeID Source # 
Instance details

Defined in Games.ECS.Prototype.PrototypeID

XMLPickler [Node] SpawnedFromPrototype Source # 
Instance details

Defined in Games.ECS.Prototype.SpawnedFromPrototype

XMLPickler [Node] Text Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] Text Source #

XMLPickler [Node] String Source # 
Instance details

Defined in Games.ECS.Serialisation

XMLPickler [Node] Integer Source # 
Instance details

Defined in Games.ECS.Serialisation

XMLPickler [Node] Natural Source # 
Instance details

Defined in Games.ECS.Serialisation

XMLPickler [Node] Bool Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] Bool Source #

XMLPickler [Node] Char Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] Char Source #

XMLPickler [Node] Double Source # 
Instance details

Defined in Games.ECS.Serialisation

XMLPickler [Node] Float Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] Float Source #

XMLPickler [Node] Int Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] Int Source #

XMLPickler [Node] Word Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] Word Source #

XMLPickler [Node] v => XMLPickler [Node] (Seq v) Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] (Seq v) Source #

(IsList a, XMLPickler [Node] (Item a)) => XMLPickler [Node] (AsList a) Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] (AsList a) Source #

(Read a, Show a) => XMLPickler [Node] (AsString a) Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] (AsString a) Source #

(Ord a, XMLPickler [Node] a) => XMLPickler [Node] (OSet a) Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] (OSet a) Source #

(Eq v, Hashable v, XMLPickler [Node] v) => XMLPickler [Node] (HashSet v) Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] (HashSet v) Source #

XMLPickler [Node] v => XMLPickler [Node] (HashMap Entity v) Source # 
Instance details

Defined in Games.ECS.Entity

Methods

xpickle :: PU [Node] (HashMap Entity v) Source #

(Eq k, Hashable k, XMLPickleAsAttribute k, XMLPickler [Node] v) => XMLPickler [Node] (HashMap k v) Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] (HashMap k v) Source #

(Eq a, KnownSymbol name, KnownSymbol (AppendSymbol name "TaggedComponent wrapper"), XMLPickler [Node] a) => XMLPickler [Node] (TaggedComponent name (Maybe a)) Source # 
Instance details

Defined in Games.ECS.Component

Methods

xpickle :: PU [Node] (TaggedComponent name (Maybe a)) Source #

(KnownSymbol name, KnownSymbol (AppendSymbol name "TaggedComponent wrapper"), XMLPickler [Node] a) => XMLPickler [Node] (TaggedComponent name a) Source # 
Instance details

Defined in Games.ECS.Component

Methods

xpickle :: PU [Node] (TaggedComponent name a) Source #

(Constructor c, GXmlPickler [Node] f) => GXmlPickler [Node] (M1 C c f) Source #

For constructors

Instance details

Defined in Games.ECS.Serialisation

Methods

gxpicklef :: PU [Node] a -> PU [Node] (M1 C c f a) Source #

gxpickleContentsf :: PU [Node] a -> PU [Node] (M1 C c f a) Source #

(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.

Instance details

Defined in Games.ECS.Entity

Methods

gxpicklef :: PU [Node] a -> PU [Node] (M1 C c'' (M1 S c (K1 i Entity :: Type -> Type)) a) Source #

gxpickleContentsf :: PU [Node] a -> PU [Node] (M1 C c'' (M1 S c (K1 i Entity :: Type -> Type)) a) Source #

(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.

Instance details

Defined in Games.ECS.Component

Methods

gxpicklef :: PU [Node] a0 -> PU [Node] (M1 D d (M1 C c'' (M1 S c (K1 i (TaggedComponent name (Maybe a)) :: Type -> Type))) a0) Source #

gxpickleContentsf :: PU [Node] a0 -> PU [Node] (M1 D d (M1 C c'' (M1 S c (K1 i (TaggedComponent name (Maybe a)) :: Type -> Type))) a0) Source #

(XMLPickler [Node] a, Selector c) => GXmlPickler [Node] (M1 S c (K1 i (Maybe a) :: Type -> Type)) Source #

For Maybe types

Instance details

Defined in Games.ECS.Serialisation

Methods

gxpicklef :: PU [Node] a0 -> PU [Node] (M1 S c (K1 i (Maybe a) :: Type -> Type) a0) Source #

gxpickleContentsf :: PU [Node] a0 -> PU [Node] (M1 S c (K1 i (Maybe a) :: Type -> Type) a0) Source #

(Selector c, GXmlPickler [Node] f) => GXmlPickler [Node] (M1 S c f) Source #

For record field selectors

Instance details

Defined in Games.ECS.Serialisation

Methods

gxpicklef :: PU [Node] a -> PU [Node] (M1 S c f a) Source #

gxpickleContentsf :: PU [Node] a -> PU [Node] (M1 S c f a) Source #

type Rep Node 
Instance details

Defined in Data.XML.Types

newtype AsString a Source #

A deriving-via helper.

Constructors

AsString 

Fields

Instances

Instances details
IsString a => IsString (AsString a) Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

fromString :: String -> AsString a #

Read a => Read (AsString a) Source # 
Instance details

Defined in Games.ECS.Serialisation

Show a => Show (AsString a) Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

showsPrec :: Int -> AsString a -> ShowS #

show :: AsString a -> String #

showList :: [AsString a] -> ShowS #

Eq a => Eq (AsString a) Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

(==) :: AsString a -> AsString a -> Bool #

(/=) :: AsString a -> AsString a -> Bool #

(IsString a, Show a) => XMLPickleAsAttribute (AsString a) Source # 
Instance details

Defined in Games.ECS.Serialisation

(Read a, Show a) => XMLPickler [Node] (AsString a) Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] (AsString a) Source #

class GXmlPickler t (f :: Type -> Type) where Source #

Generic pickling support.

Minimal complete definition

gxpickleContentsf

Methods

gxpicklef :: PU t a -> PU t (f a) Source #

gxpickleContentsf :: PU t a -> PU t (f a) Source #

Instances

Instances details
(GXmlPickler t f, GXmlPickler t g) => GXmlPickler t (f :+: g) Source #

For sums of constructors

Instance details

Defined in Games.ECS.Serialisation

Methods

gxpicklef :: PU t a -> PU t ((f :+: g) a) Source #

gxpickleContentsf :: PU t a -> PU t ((f :+: g) a) Source #

XMLPickler t a => GXmlPickler t (K1 i a :: Type -> Type) Source #

For individual fields

Instance details

Defined in Games.ECS.Serialisation

Methods

gxpicklef :: PU t a0 -> PU t (K1 i a a0) Source #

gxpickleContentsf :: PU t a0 -> PU t (K1 i a a0) Source #

(Datatype d, GXmlPickler t f) => GXmlPickler t (M1 D d f) Source #

For datatypes

Instance details

Defined in Games.ECS.Serialisation

Methods

gxpicklef :: PU t a -> PU t (M1 D d f a) Source #

gxpickleContentsf :: PU t a -> PU t (M1 D d f a) Source #

GXmlPickler [t] (U1 :: Type -> Type) Source #

For empty constructors

Instance details

Defined in Games.ECS.Serialisation

Methods

gxpicklef :: PU [t] a -> PU [t] (U1 a) Source #

gxpickleContentsf :: PU [t] a -> PU [t] (U1 a) Source #

(GXmlPickler [t] f, GXmlPickler [t] g) => GXmlPickler [t] (f :*: g) Source #

For products of fields

Instance details

Defined in Games.ECS.Serialisation

Methods

gxpicklef :: PU [t] a -> PU [t] ((f :*: g) a) Source #

gxpickleContentsf :: PU [t] a -> PU [t] ((f :*: g) a) Source #

(Constructor c, GXmlPickler [Node] f) => GXmlPickler [Node] (M1 C c f) Source #

For constructors

Instance details

Defined in Games.ECS.Serialisation

Methods

gxpicklef :: PU [Node] a -> PU [Node] (M1 C c f a) Source #

gxpickleContentsf :: PU [Node] a -> PU [Node] (M1 C c f a) Source #

(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.

Instance details

Defined in Games.ECS.Entity

Methods

gxpicklef :: PU [Node] a -> PU [Node] (M1 C c'' (M1 S c (K1 i Entity :: Type -> Type)) a) Source #

gxpickleContentsf :: PU [Node] a -> PU [Node] (M1 C c'' (M1 S c (K1 i Entity :: Type -> Type)) a) Source #

(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.

Instance details

Defined in Games.ECS.Component

Methods

gxpicklef :: PU [Node] a0 -> PU [Node] (M1 D d (M1 C c'' (M1 S c (K1 i (TaggedComponent name (Maybe a)) :: Type -> Type))) a0) Source #

gxpickleContentsf :: PU [Node] a0 -> PU [Node] (M1 D d (M1 C c'' (M1 S c (K1 i (TaggedComponent name (Maybe a)) :: Type -> Type))) a0) Source #

(XMLPickler [Node] a, Selector c) => GXmlPickler [Node] (M1 S c (K1 i (Maybe a) :: Type -> Type)) Source #

For Maybe types

Instance details

Defined in Games.ECS.Serialisation

Methods

gxpicklef :: PU [Node] a0 -> PU [Node] (M1 S c (K1 i (Maybe a) :: Type -> Type) a0) Source #

gxpickleContentsf :: PU [Node] a0 -> PU [Node] (M1 S c (K1 i (Maybe a) :: Type -> Type) a0) Source #

(Selector c, GXmlPickler [Node] f) => GXmlPickler [Node] (M1 S c f) Source #

For record field selectors

Instance details

Defined in Games.ECS.Serialisation

Methods

gxpicklef :: PU [Node] a -> PU [Node] (M1 S c f a) Source #

gxpickleContentsf :: PU [Node] a -> PU [Node] (M1 S c f a) Source #

formatElement :: String -> String Source #

Format field names nicely

newtype AsList a Source #

A deriving-via helper.

Constructors

AsList 

Fields

Instances

Instances details
IsList a => IsList (AsList a) Source # 
Instance details

Defined in Games.ECS.Serialisation

Associated Types

type Item (AsList a) 
Instance details

Defined in Games.ECS.Serialisation

type Item (AsList a) = Identity (Item a)

Methods

fromList :: [Item (AsList a)] -> AsList a #

fromListN :: Int -> [Item (AsList a)] -> AsList a #

toList :: AsList a -> [Item (AsList a)] #

Show a => Show (AsList a) Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

showsPrec :: Int -> AsList a -> ShowS #

show :: AsList a -> String #

showList :: [AsList a] -> ShowS #

(IsList a, XMLPickler [Node] (Item a)) => XMLPickler [Node] (AsList a) Source # 
Instance details

Defined in Games.ECS.Serialisation

Methods

xpickle :: PU [Node] (AsList a) Source #

type Item (AsList a) Source # 
Instance details

Defined in Games.ECS.Serialisation

type Item (AsList a) = Identity (Item 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 Source #

Pickle adapter for Selector

optElemD :: forall t i (s :: Meta) (f :: Type -> Type) p a. Datatype s => PU [Node] a -> t i s f p -> PU [Node] a Source #

Pickle adapter for Datatype

optElemC :: forall t i (s :: Meta) (f :: Type -> Type) p a. Constructor s => PU [Node] a -> t i s f p -> PU [Node] a Source #

Pickle adapter for Constructor