music-score-1.7.1: Musical score and part representation.

Portabilitynon-portable (TF,GNTD)
Stabilityexperimental
Maintainerhans@hanshoglund.se
Safe HaskellNone

Music.Time.Meta

Contents

Description

Provides a way to annotate data-types with Transformable meta-data. See Music.Score.Meta for more specific applications.

Inspired by Clojure and Diagram's styles, in turn based on xmonad's Message type, in turn based on ideas in:

Simon Marlow. An Extensible Dynamically-Typed Hierarchy of Exceptions. Proceedings of the 2006 ACM SIGPLAN workshop on Haskell. http://research.microsoft.com/apps/pubs/default.aspx?id=67968.

Synopsis

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.

data Attribute Source

An existential wrapper type to hold attributes.

Creating attributes

wrapAttr :: AttributeClass a => a -> AttributeSource

Wrap up an attribute.

wrapTAttr :: TAttributeClass a => a -> AttributeSource

Wrap up a transformable attribute.

unwrapAttr :: AttributeClass a => Attribute -> Maybe aSource

Convert something from an attribute. Also works with transformable attributes

Meta-data

data Meta Source

Instances

Show Meta 
Monoid Meta

The empty meta contains no attributes; composition of metas is a union of attributes; if the two metas have attributes of the same type they are combined according to their semigroup structure.

Semigroup Meta 
Transformable Meta 
Splittable Meta 
Reversible Meta 
HasMeta Meta 

Creating meta-data

wrapMeta :: forall a. AttributeClass a => a -> MetaSource

Convert something from meta-data. Also works with transformable attributes

wrapTMeta :: forall a. TAttributeClass a => a -> MetaSource

Convert something to meta-data.

unwrapMeta :: forall a. AttributeClass a => Meta -> Maybe aSource

Convert something from meta-data.

The HasMeta class

class HasMeta a whereSource

Type class for things which have meta-data.

Methods

meta :: Lens' a MetaSource

Access the meta-data.

Instances

HasMeta Meta 
HasMeta a => HasMeta (Maybe a) 
HasMeta (AddMeta a) 
HasMeta (Score a) 
HasMeta a => HasMeta (b, a) 
HasMeta a => HasMeta (Twain b a) 

setMeta :: HasMeta a => Meta -> a -> aSource

setMetaAttr :: (AttributeClass b, HasMeta a) => b -> a -> aSource

Update a meta attribute.

setMetaTAttr :: (TAttributeClass b, HasMeta a) => b -> a -> aSource

Update a meta attribute.

applyMeta :: HasMeta a => Meta -> a -> aSource

Apply meta-information by combining it (on the left) with the existing meta-information.

Add meta-data to arbitrary types

data AddMeta a Source

Annotate an arbitrary type with meta-data, preserving instances of all common type classes. In particular Functor and Applicative is lifted and Compose AddMeta is semantically equivalent to Identity.

Instances

Monad AddMeta 
Functor AddMeta 
Typeable1 AddMeta 
Applicative AddMeta 
Foldable AddMeta 
Comonad AddMeta 
Bounded a => Bounded (AddMeta a) 
Enum a => Enum (AddMeta a) 
Eq a => Eq (AddMeta a) 
Floating a => Floating (AddMeta a) 
Fractional a => Fractional (AddMeta a) 
Integral a => Integral (AddMeta a) 
Num a => Num (AddMeta a) 
Ord a => Ord (AddMeta a) 
Real a => Real (AddMeta a) 
RealFrac a => RealFrac (AddMeta a) 
Show a => Show (AddMeta a) 
Monoid a => Monoid (AddMeta a) 
Semigroup a => Semigroup (AddMeta a) 
Wrapped (AddMeta a) 
Transformable a => Transformable (AddMeta a) 
HasDuration a => HasDuration (AddMeta a) 
HasPosition a => HasPosition (AddMeta a) 
Splittable a => Splittable (AddMeta a) 
Reversible a => Reversible (AddMeta a) 
HasMeta (AddMeta a) 
Rewrapped (AddMeta a) (AddMeta b) 

annotated :: Lens (AddMeta a) (AddMeta b) a bSource

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 bSource

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