Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
Synopsis
- type TypeName = String
- type ConstructorName = String
- type TypeVersion = Word32
- data Structure
- type SopStructure = [(ConstructorName, [Structure])]
- hashStructure :: Structure -> MD5
- typeVersion :: Functor f => (TypeVersion -> f TypeVersion) -> Structure -> f Structure
- typeName :: Functor f => (TypeName -> f TypeName) -> Structure -> f Structure
- structureBuilder :: Structure -> Builder
- class Typeable a => Structured a where
- structureHash :: forall a. Structured a => Proxy a -> MD5
- nominalStructure :: Typeable a => Proxy a -> Structure
- containerStructure :: forall f a. (Typeable f, Structured a) => Proxy (f a) -> Structure
- genericStructure :: forall a. (Typeable a, Generic a, GStructured (Rep a)) => Proxy a -> Structure
- class GStructured (f :: Type -> Type) where
- gstructured :: TypeRep -> Proxy f -> TypeVersion -> Structure
- class GStructuredSum (f :: Type -> Type) where
- gstructuredSum :: Proxy f -> SopStructure -> SopStructure
- class GStructuredProd (f :: Type -> Type) where
- gstructuredProd :: Proxy f -> [Structure] -> [Structure]
Documentation
type ConstructorName = String Source #
type TypeVersion = Word32 Source #
A sematic version of a data type. Usually 0.
Structure of a datatype.
It can be infinite, as far as TypeRep
s involved are finite.
(e.g. polymorphic recursion might cause troubles).
Nominal !TypeRep !TypeVersion TypeName [Structure] | nominal, yet can be parametrised by other structures. |
Newtype !TypeRep !TypeVersion TypeName Structure | a newtype wrapper |
Structure !TypeRep !TypeVersion TypeName SopStructure | sum-of-products structure |
Instances
type SopStructure = [(ConstructorName, [Structure])] Source #
typeVersion :: Functor f => (TypeVersion -> f TypeVersion) -> Structure -> f Structure Source #
A van-Laarhoven lens into TypeVersion
of Structure
typeVersion
:: Lens'Structure
TypeVersion
structureBuilder :: Structure -> Builder Source #
class Typeable a => Structured a where Source #
Class of types with a known Structure
.
For regular data types Structured
can be derived generically.
data Record = Record { a :: Int, b :: Bool, c :: [Char] } deriving (Generic
) instanceStructured
Record
Since: 3.2.0.0
Nothing
structure :: Proxy a -> Structure Source #
structure :: (Generic a, GStructured (Rep a)) => Proxy a -> Structure Source #
structureHash' :: Tagged a MD5 Source #
Instances
structureHash :: forall a. Structured a => Proxy a -> MD5 Source #
Semantically
.hashStructure
. structure
containerStructure :: forall f a. (Typeable f, Structured a) => Proxy (f a) -> Structure Source #
genericStructure :: forall a. (Typeable a, Generic a, GStructured (Rep a)) => Proxy a -> Structure Source #
Derive structure
genrically.
class GStructured (f :: Type -> Type) where Source #
Used to implement genericStructure
.
gstructured :: TypeRep -> Proxy f -> TypeVersion -> Structure Source #
Instances
(i ~ D, Datatype c, GStructuredSum f) => GStructured (M1 i c f) Source # | |
Defined in Data.Structured.Internal gstructured :: TypeRep -> Proxy (M1 i c f) -> TypeVersion -> Structure Source # |
class GStructuredSum (f :: Type -> Type) where Source #
gstructuredSum :: Proxy f -> SopStructure -> SopStructure Source #
Instances
GStructuredSum (V1 :: Type -> Type) Source # | |
Defined in Data.Structured.Internal gstructuredSum :: Proxy V1 -> SopStructure -> SopStructure Source # | |
(GStructuredSum f, GStructuredSum g) => GStructuredSum (f :+: g) Source # | |
Defined in Data.Structured.Internal gstructuredSum :: Proxy (f :+: g) -> SopStructure -> SopStructure Source # | |
(i ~ C, Constructor c, GStructuredProd f) => GStructuredSum (M1 i c f) Source # | |
Defined in Data.Structured.Internal gstructuredSum :: Proxy (M1 i c f) -> SopStructure -> SopStructure Source # |
class GStructuredProd (f :: Type -> Type) where Source #
Instances
GStructuredProd (U1 :: Type -> Type) Source # | |
Defined in Data.Structured.Internal | |
Structured c => GStructuredProd (K1 i c :: Type -> Type) Source # | |
Defined in Data.Structured.Internal | |
(GStructuredProd f, GStructuredProd g) => GStructuredProd (f :*: g) Source # | |
Defined in Data.Structured.Internal | |
(i ~ S, GStructuredProd f) => GStructuredProd (M1 i c f) Source # | |
Defined in Data.Structured.Internal |