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

Copyright(c) Hans Hoglund 2012–2014
LicenseBSD-style
Maintainerhans@hanshoglund.se
Stabilityexperimental
Portabilitynon-portable (TF,GNTD)
Safe HaskellNone
LanguageHaskell2010

Music.Time.Meta

Contents

Description

Provides a way to annotate data-types with Transformable meta-data. Inspired by Clojure meta-data and Diagrams styles.

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

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

class HasMeta a where Source

Type class for things which have meta-data.

Methods

meta :: Lens' a Meta Source

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) 

getMeta :: HasMeta a => a -> Meta Source

Extract meta-data.

mapMeta :: HasMeta a => (Meta -> Meta) -> a -> a Source

Map over meta-data.

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

Update meta-data.

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

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.

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