Copyright | (c) Hans Hoglund 2012–2014 |
---|---|
License | BSD-style |
Maintainer | hans@hanshoglund.se |
Stability | experimental |
Portability | non-portable (TF,GNTD) |
Safe Haskell | None |
Language | Haskell2010 |
Provides a way to annotate data-types with Transformable
meta-data.
Inspired by Clojure meta-data and Diagrams styles.
- type AttributeClass a = (Typeable a, Monoid a, Semigroup a)
- type TAttributeClass a = (Transformable a, AttributeClass a)
- data Attribute :: *
- wrapAttr :: AttributeClass a => a -> Attribute
- wrapTAttr :: TAttributeClass a => a -> Attribute
- unwrapAttr :: AttributeClass a => Attribute -> Maybe a
- data Meta
- wrapMeta :: forall a. AttributeClass a => a -> Meta
- wrapTMeta :: forall a. TAttributeClass a => a -> Meta
- unwrapMeta :: forall a. AttributeClass a => Meta -> Maybe a
- class HasMeta a where
- getMeta :: HasMeta a => a -> Meta
- mapMeta :: HasMeta a => (Meta -> Meta) -> a -> a
- setMeta :: HasMeta a => Meta -> a -> a
- metaTypes :: HasMeta a => a -> [String]
- applyMeta :: HasMeta a => Meta -> a -> a
- setMetaAttr :: (AttributeClass b, HasMeta a) => b -> a -> a
- setMetaTAttr :: (TAttributeClass b, HasMeta a) => b -> a -> a
- preserveMeta :: (HasMeta a, HasMeta b) => (a -> b) -> a -> b
- data AddMeta a
- annotated :: Lens (AddMeta a) (AddMeta b) a b
- unannotated :: Getter a (AddMeta a)
- unsafeAnnotated :: Iso (AddMeta a) (AddMeta b) a b
Attributes
type AttributeClass a = (Typeable a, Monoid a, Semigroup a) Source
Class of values that can be wrapped.
type TAttributeClass a = (Transformable a, AttributeClass a) Source
Class of values that can be wrapped and transformed.
An existential wrapper type to hold attributes.
Creating attributes
wrapAttr :: AttributeClass a => a -> Attribute Source
Wrap up an attribute.
wrapTAttr :: TAttributeClass a => a -> Attribute Source
Wrap up a transformable attribute.
unwrapAttr :: AttributeClass a => Attribute -> Maybe a Source
Convert something from an attribute. Also works with transformable attributes
Meta-data
Creating meta-data
wrapMeta :: forall a. AttributeClass a => a -> Meta Source
Convert something from meta-data. Also works with transformable attributes
wrapTMeta :: forall a. TAttributeClass a => a -> Meta Source
Convert something to meta-data.
unwrapMeta :: forall a. AttributeClass a => Meta -> Maybe a Source
Convert something from meta-data.
The HasMeta class
Type class for things which have meta-data.
metaTypes :: HasMeta a => a -> [String] Source
Show the types of meta-data attachd to this value. Useful for debugging.
applyMeta :: HasMeta a => Meta -> a -> a Source
Apply meta-information by combining it with existing meta-information.
setMetaAttr :: (AttributeClass b, HasMeta a) => b -> a -> a Source
Update a meta attribute.
setMetaTAttr :: (TAttributeClass b, HasMeta a) => b -> a -> a Source
Update a meta attribute.
preserveMeta :: (HasMeta a, HasMeta b) => (a -> b) -> a -> b Source
Apply a function without affecting meta-data.
Add meta-data to arbitrary types
Annotate an arbitrary type with meta-data, preserving instances of
all common type classes. In particular Functor
and Applicative
is lifted and
is semantically equivalent to Compose
AddMeta
Identity
.
annotated :: Lens (AddMeta a) (AddMeta b) a b Source
Access the annotated value.
over annotated = fmap
unannotated :: Getter a (AddMeta a) Source
Access the annotated value.
view fromAnnotated = pure
unsafeAnnotated :: Iso (AddMeta a) (AddMeta b) a b Source
Access the annotated value. This is only an isomorphism up to meta-data
equivalence. In particular under unsafeAnnotated
leads to meta-data being
thrown away. See annotated
and unannotated
for safe (but less general)
definitions.
over annotated = fmap