temporal-media-0.2.1: data types for temporal media

Temporal.Media

Contents

Description

An embedded domain-specific language (EDSL) for creating lists of constant time events related in time. Combinators are optimized in fusion style.

Synopsis

Introduction

Temporal.Media is an embedded domain-specific language (EDSL) 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 Media. It provides interface to compose list of events. There is optimization that goes on behind the scene.

  • Fusion
fmap f . fmap g 

is trasformed to

fmap (f . g) 

same holds for more general eventMap.

  • Loops

Transformations on loop 's are executed only for one cycle.

  • Structure functions

Structure functions (sequent, parallel, stretch, reverseM) are rendered as linear transformations of time and duration of an event.

Example of usage can be found in package 'temporal-music-notation' [1]. Score module is based on this library.

[1] http://hackage.haskell.org/package/temporal-music-notation

Types

class (Ord a, Num a, Fractional a) => Dur a Source

class of time values

Instances

data Media t a Source

Media is core data type. Essentially Media provides functional interface to EventList construction.

Instances

data Event t a Source

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

Constructors

Event 

Fields

eventStart :: t
 
eventDur :: t
 
eventContent :: a
 

Instances

Functor (Event t) 
(Eq t, Eq a) => Eq (Event t a) 
(Show t, Show a) => Show (Event t a) 

data EventList t a Source

List of Event s. First argument stands for total duration of EventList.

Constructors

EventList t [Event t a] 

Instances

Functor (EventList t) 
(Eq t, Eq a) => Eq (EventList t a) 
(Show t, Show a) => Show (EventList t a) 

Constructors

none :: Dur t => t -> Media t aSource

none constructs an empty event. Nothing is going on for a given time.

temp :: Dur t => t -> a -> Media t aSource

temp constructs just an event. Value of type a lasts for some time.

Composition

(+:+) :: Dur t => Media t a -> Media t a -> Media t aSource

Binary sequent composition. In (a+:+b) a happens first and then b goes.

(=:=) :: Dur t => Media t a -> Media t a -> Media t aSource

Binary parallel composition. In (a=:=b) a and b happen simultaneously.

(=:/) :: Dur t => Media t a -> Media t a -> Media t aSource

Truncating binary composition. In (a=:/b), a and b happen simultaneously but whole result lasts only for min (dur a) (dur b) time.

sequent :: Dur t => [Media t a] -> Media t aSource

Sequent composition on lists.

parallel :: Dur t => [Media t a] -> Media t aSource

Parallel composition on lists.

parallelT :: Dur t => [Media t a] -> Media t aSource

Truncating parallel composition on lists.

delay :: Dur t => t -> Media t a -> Media t aSource

delay appends block of nothing of given duration to the begging of value (if duration is positive) or to the end of value (if duration is negative).

loop :: Dur t => Int -> Media t a -> Media t aSource

loop repeats sequentially given value.

Transformations

stretch :: Dur t => t -> Media t a -> Media t aSource

Stretching values by factor.

reverseM :: Media t a -> Media t aSource

Reverses input.

slice :: Dur t => t -> t -> Media t a -> Media t aSource

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

takeM :: Dur t => t -> Media t a -> Media t aSource

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

dropM :: Dur t => t -> Media t a -> Media t aSource

(dropM t m) is equivalent to (slice t (dur m) m).

Mappings

eventMap :: (Event t a -> Event t a') -> Media t a -> Media t a'Source

General mapping. In the end all values of type Media are to be converted to EventList wich is list of Event s and function eventMap allows mapping on Media subvalues as if they are events already.

Warning : It is possible to change start time position with eventMap but it can lead to unexpected outcome when used with slice function. slice operates on structure of type Media (how value was built with sequent, parallel or stretch and other functions), but eventMap operates on Media subvalues as if they are converted to Event s and some shifted events can slip through slice 's fingers.

tmap :: (t -> a -> b) -> Media t a -> Media t bSource

map with time

dmap :: (t -> a -> b) -> Media t a -> Media t bSource

map with duration

tdmap :: (t -> t -> a -> b) -> Media t a -> Media t bSource

map with time and duration

tmapRel :: Dur t => (t -> a -> b) -> Media t a -> Media t bSource

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

dmapRel :: Dur t => (t -> a -> b) -> Media t a -> Media t bSource

Relative dmap.

tdmapRel :: Dur t => (t -> t -> a -> b) -> Media t a -> Media t bSource

Relative tdmap.

Rendering

dur :: Media t a -> tSource

Duration querry.

renderMedia :: Dur t => Media t a -> EventList t aSource

renderMedia converts values of type Media to values of type EventList. If some values have negative time (it is possible through eventMap) all events are shifted so that first event has zero start time. Events are unsorted by start time.

Miscellaneous

linseg :: (Ord t, Fractional t) => [t] -> t -> tSource

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

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

a, b, c ... - values

da, db, ... - duration of segments