music-score-1.9.0: 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 
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

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.

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

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 
Applicative AddMeta 
Foldable AddMeta 
Traversable AddMeta

A Event is a value with an onset and and offset in time. It is an instance of Transformable.

You can use value to apply a function in the context of the transformation, i.e.

over value (* line) (delay 2 $ return line)
(view value) . transform s = transform s . (view value)
Comonad AddMeta 
Eq1 AddMeta 
Ord1 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) 
Typeable (* -> *) AddMeta 
type Unwrapped (AddMeta a) = Twain Meta a 

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