temporal-media-0.6.2: data types for temporal media

Safe HaskellSafe
LanguageHaskell98

Temporal.Media

Contents

Description

A library for creating lists of constant time events related in time.

Synopsis

Introduction

Temporal.Media is a library for creating lists of constant time events related in time. Constant time event is value that starts at some fixed time and lasts for some fixed time. Library provides functions to build lists of such events with time-relations like sequent, parallel or delayed.

Core type of library is Track. It provides interface to compose list of events.

Types

data Event t a Source #

Constant time events. Value a starts at some time and lasts for some time.

Constructors

Event 

Fields

Instances

Functor (Event t) Source # 

Methods

fmap :: (a -> b) -> Event t a -> Event t b #

(<$) :: a -> Event t b -> Event t a #

(Eq a, Eq t) => Eq (Event t a) Source # 

Methods

(==) :: Event t a -> Event t a -> Bool #

(/=) :: Event t a -> Event t a -> Bool #

(Show a, Show t) => Show (Event t a) Source # 

Methods

showsPrec :: Int -> Event t a -> ShowS #

show :: Event t a -> String #

showList :: [Event t a] -> ShowS #

data Track t a Source #

Track is a set of Event s. There is total duration of the track, but Events can go beyond the scope of total duration (as a result of mapEvents function). Total duration is used in sequent composition of tracks.

Instances

Functor (Track t) Source # 

Methods

fmap :: (a -> b) -> Track t a -> Track t b #

(<$) :: a -> Track t b -> Track t a #

Foldable (Track t) Source # 

Methods

fold :: Monoid m => Track t m -> m #

foldMap :: Monoid m => (a -> m) -> Track t a -> m #

foldr :: (a -> b -> b) -> b -> Track t a -> b #

foldr' :: (a -> b -> b) -> b -> Track t a -> b #

foldl :: (b -> a -> b) -> b -> Track t a -> b #

foldl' :: (b -> a -> b) -> b -> Track t a -> b #

foldr1 :: (a -> a -> a) -> Track t a -> a #

foldl1 :: (a -> a -> a) -> Track t a -> a #

toList :: Track t a -> [a] #

null :: Track t a -> Bool #

length :: Track t a -> Int #

elem :: Eq a => a -> Track t a -> Bool #

maximum :: Ord a => Track t a -> a #

minimum :: Ord a => Track t a -> a #

sum :: Num a => Track t a -> a #

product :: Num a => Track t a -> a #

Traversable (Track t) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Track t a -> f (Track t b) #

sequenceA :: Applicative f => Track t (f a) -> f (Track t a) #

mapM :: Monad m => (a -> m b) -> Track t a -> m (Track t b) #

sequence :: Monad m => Track t (m a) -> m (Track t a) #

(Eq a, Eq t) => Eq (Track t a) Source # 

Methods

(==) :: Track t a -> Track t a -> Bool #

(/=) :: Track t a -> Track t a -> Bool #

(Show a, Show t) => Show (Track t a) Source # 

Methods

showsPrec :: Int -> Track t a -> ShowS #

show :: Track t a -> String #

showList :: [Track t a] -> ShowS #

(Num t, IfB t, OrdB t) => Monoid (Track t a) Source # 

Methods

mempty :: Track t a #

mappend :: Track t a -> Track t a -> Track t a #

mconcat :: [Track t a] -> Track t a #

(Num t, IfB t, OrdB t) => Rest (Track t a) Source #

Empty track that lasts for some time.

Methods

rest :: DurOf (Track t a) -> Track t a Source #

Num t => Stretch (Track t a) Source #

Stretches track in time domain.

Methods

str :: DurOf (Track t a) -> Track t a -> Track t a Source #

Num t => Delay (Track t a) Source #

Delays all events by given duration.

Methods

del :: DurOf (Track t a) -> Track t a -> Track t a Source #

(Num t, IfB t, OrdB t) => Compose (Track t a) Source # 
(Num t, IfB t, OrdB t) => Harmony (Track t a) Source # 

Methods

har :: [Track t a] -> Track t a Source #

(=:=) :: Track t a -> Track t a -> Track t a Source #

(Num t, IfB t, OrdB t) => Melody (Track t a) Source # 

Methods

mel :: [Track t a] -> Track t a Source #

(+:+) :: Track t a -> Track t a -> Track t a Source #

Duration (Track t a) Source # 

Methods

dur :: Track t a -> DurOf (Track t a) Source #

type DurOf (Track t a) Source # 
type DurOf (Track t a) = t

within :: Real t => t -> t -> Event t a -> Bool Source #

Tests if given Event happens between two time stamps.

eventEnd :: Num t => Event t a -> t Source #

End point of event (start time plus duration).

Composition

temp :: Num t => a -> Track t a Source #

temp constructs just an event. Value of type a lasts for one time unit and starts at zero.

fromEvent :: Num t => Event t a -> Track t a Source #

Constructs a track that contains a single event.

singleEvent :: Num t => t -> t -> a -> Track t a Source #

Constructs a track that contains a single event.

singleEvent start duration content

reflect :: (Num t, IfB t, OrdB t) => Track t a -> Track t a Source #

Reversing the tracks

(=:/) :: (Real t, IfB t, OrdB t) => Track t a -> Track t a -> Track t a Source #

Turncating parallel composition. Total duration equals to minimum of the two tracks. All events that goes beyond the limit are dropped.

harT :: (Real t, IfB t, OrdB t) => [Track t a] -> Track t a Source #

Turncating parallel composition on list of tracks.

sustain :: Num t => t -> Track t a -> Track t a Source #

After this transformation events last longer by some constant amount of time.

sustainT :: (Ord t, Num t) => t -> Track t a -> Track t a Source #

Prolongated events can not exceed total track duration. All event are sustained but those that are close to end of the track are sliced. It resembles sustain on piano, when track ends you release the pedal.

Common patterns

melTemp :: (Num t, IfB t, OrdB t) => [a] -> Track t a Source #

Analog of replicate function for tracks. Replicated tracks are played sequentially.

A melody of events. Each of them lasts for one second.

harTemp :: (Num t, IfB t, OrdB t) => [a] -> Track t a Source #

A chord of events. Each of them lasts for one second.

harTMap :: (Real t, IfB t, OrdB t) => (a -> Track t b) -> [a] -> Track t b Source #

Transforms a sequence and then applies a harT.

Filtering

slice :: Real t => t -> t -> Track t a -> Track t a Source #

slice cuts piece of value within given time interval. for (slice t0 t1 m), if t1 < t0 result is reversed. If t0 is negative or t1 goes beyond dur m blocks of nothing inserted so that duration of result equals to abs (t0 - t1).

takeT :: Real t => t -> Track t a -> Track t a Source #

(takeT t) is equivalent to (slice 0 t).

dropT :: Real t => t -> Track t a -> Track t a Source #

(dropT t m) is equivalent to (slice t (dur a) a).

filterEvents :: Real t => (Event t a -> Bool) -> Track t a -> Track t a Source #

Filter track.

Mappings

mapEvents :: Num t => (Event t a -> Event t b) -> Track t a -> Track t b Source #

General mapping. Maps not only values but events.

traverseEvents :: (Num t1, Applicative f) => (t1 -> f t2) -> (Event t1 a -> f (Event t2 b)) -> Track t1 a -> f (Track t2 b) Source #

tmap :: Real t => (Event t a -> b) -> Track t a -> Track t b Source #

Maps values and time stamps.

tmapRel :: RealFrac t => (Event t a -> b) -> Track t a -> Track t b Source #

Relative tmap. Time values are normalized by argument's duration.

Rendering

render :: Num t => Track t a -> [Event t a] Source #

Get all events on recordered on the track.

alignByZero :: Real t => [Event t a] -> [Event t a] Source #

Shifts all events so that minimal start time equals to zero if first event has negative start time.

sortEvents :: Ord t => [Event t a] -> [Event t a] Source #

Sorts all events by start time.

Monoid synonyms

This package heavily relies on Monoids, so there are shorcuts for Monoid methods.

nil :: Monoid a => a Source #

Synonym for method mempty.

Miscellaneous

linfun :: (Ord t, Fractional t) => [t] -> t -> t Source #

Linear interpolation. Can be useful with mapEvents for envelope changes.

linfun [a, da, b, db, c, ... ]

a, b, c ... - values

da, db, ... - duration of segments

linfunRel :: (Ord t, Fractional t) => t -> [t] -> t -> t Source #

With linfunRel you can make linear interpolation function that has equal distance between points. First argument gives total length of the interpolation function and second argument gives list of values. So call

linfunRel dur [a1, a2, a3, ..., aN]

is equivalent to:

linfun [a1, dur/N, a2, dur/N, a3, ..., dur/N, aN]