temporal-media-0.0: data types for temporal media

Temporal.Media

Contents

Synopsis

Time classes

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

time class

Instances

class Dur t => Temporal t a whereSource

Temporal structures

Methods

noneSource

Arguments

:: t 
-> a

absence of value

durSource

Arguments

:: a 
-> t

duration of value

Instances

Dur t => Temporal t (Unit t a) 
Dur t => Temporal t (EventList t a) 
Temporal t a => Temporal t (Media c a) 
Dur t => Temporal t (MediaUnit t c a) 

class Dur t => Stretchable t a whereSource

Stretching values by given time-factor

Methods

stretch :: t -> a -> aSource

Instances

Dur t => Stretchable t (Unit t a) 
(Dur t, Stretchable t a) => Stretchable t (EventList t a) 
Stretchable t a => Stretchable t (Media c a) 
Dur t => Stretchable t (MediaUnit t c a) 

class ToMaybe m whereSource

Values covertible to Maybe

auxiliary class for conversion to EventList

Methods

toMaybe :: m a -> Maybe aSource

Instances

Dur t => ToMaybe (Unit t) 

class Dur t => TemporalFunctor t f whereSource

temporal map

Methods

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

Instances

Transformers

class Reversible a whereSource

Methods

reverse :: a -> aSource

Instances

Dur t => Reversible (Unit t a) 
Reversible a => Reversible (Media c a) 
Dur t => Reversible (MediaUnit t c a) 

class Temporal t a => Sliceable t a whereSource

extracting parts, minimal complete definition: slice.

Methods

sliceSource

Arguments

:: t 
-> t 
-> a 
-> a

slice t0 t1 v extracts part of v inside [t0, t1]

take :: t -> a -> aSource

drop :: t -> a -> aSource

Instances

Dur t => Sliceable t (Unit t a) 
Sliceable t a => Sliceable t (Media c a) 
Dur t => Sliceable t (MediaUnit t c a) 

cut :: (Reversible a, Sliceable t a) => t -> t -> a -> aSource

mixing slice and reverse.

cut t0 t1 v - if t1 < t0 reverses result of slice

Structure

class Construct m whereSource

constructor for generic structures

Methods

prim :: a -> m aSource

Instances

Dur t => Construct (Unit t) 
Dur t => Construct (EventList t) 
Construct (Media c) 
Dur t => Construct (MediaUnit t c) 

class Arrangeable a whereSource

composing structures in sequent and parallel ways

Methods

(+:+) :: a -> a -> aSource

(=:=) :: a -> a -> aSource

Instances

class Controlable c a whereSource

modifer

Methods

control :: c -> a -> aSource

Instances

Dur t => Controlable () (EventList t a) 
Controlable c (Media c a) 
Dur t => Controlable c (MediaUnit t c a) 

sequent :: Arrangeable a => [a] -> aSource

parallel :: Arrangeable a => [a] -> aSource

loop :: Arrangeable a => Int -> a -> aSource

delay :: (Temporal t a, Arrangeable a) => t -> a -> aSource

temp :: (Construct m, Temporal t (m a), Stretchable t (m a)) => t -> a -> m aSource

constructs generic temporal structure m a form time t and initial value a

Media

data Media c a Source

Data type to represent temporal media

Constructors

Prim a

single value

(Media c a) :+: (Media c a)

sequential composition

(Media c a) :=: (Media c a)

parallel composition

Control c (Media c a)

specific environment modifier

Instances

Controlable c (Media c a) 
Sliceable t a => Sliceable t (Media c a) 
Stretchable t a => Stretchable t (Media c a) 
Temporal t a => Temporal t (Media c a) 
Monad (Media c) 
Functor (Media c) 
Applicative (Media c) 
Construct (Media c) 
(Eq c, Eq a) => Eq (Media c a) 
(Show c, Show a) => Show (Media c a) 
Arrangeable (Media c a) 
Reversible a => Reversible (Media c a) 

fold :: (a -> b) -> (b -> b -> b) -> (b -> b -> b) -> (c -> b -> b) -> Media c a -> bSource

Folding Media

 fold prim seq par mod x
  • prim - responds to Prim
  • seq - responds to :+:
  • par - responds to :=:
  • mod - responds to Control

fromMedia :: Arrangeable b => (a -> b) -> (c -> b -> b) -> Media c a -> bSource

Media imterpretation

given two functions (to convert elementary value (a -> b), and to convert modifiers (c -> b -> b)) fromMedia interprets Media structure

Simple interperetation

Event list

type Event t a = (t, t, a)Source

Event type

(t, dt, a) - value a starts at t and lasts for dt

data EventList t a Source

list of events with given total time

Constructors

EventList t [Event t a] 

Instances

Dur t => TemporalFunctor t (EventList t) 
Dur t => Controlable () (EventList t a) 
(Dur t, Stretchable t a) => Stretchable t (EventList t a) 
Dur t => Temporal t (EventList t a) 
Dur t => Functor (EventList t) 
Dur t => Construct (EventList t) 
(Eq t, Eq a) => Eq (EventList t a) 
(Show t, Show a) => Show (EventList t a) 
Dur t => Arrangeable (EventList t a) 

mapEvent :: Dur t => (a -> b) -> Event t a -> Event t bSource

toEvent :: (Temporal t (m a), ToMaybe m) => m a -> EventList t aSource

toEventList :: (Temporal t (m a), ToMaybe m) => (c -> EventList t a -> EventList t a) -> Media c (m a) -> EventList t aSource

converting to EventList

toEventList mapps generic temporal value (m a) that can be represented with (t, Maybe a) to EventList

Unit Temporal Media

data Dur t => MediaUnit t c a Source

Media with explicit time

Value is unit (undividable, invariant to reverse and time stretching) O(1) dur

Constructors

MediaUnit t (Media c (Unit t a)) 

Instances

Dur t => TemporalFunctor t (MediaUnit t c) 
Dur t => Controlable c (MediaUnit t c a) 
Dur t => Sliceable t (MediaUnit t c a) 
Dur t => Stretchable t (MediaUnit t c a) 
Dur t => Temporal t (MediaUnit t c a) 
Dur t => Monad (MediaUnit t c) 
Dur t => Functor (MediaUnit t c) 
Dur t => Applicative (MediaUnit t c) 
Dur t => Construct (MediaUnit t c) 
Dur t => Arrangeable (MediaUnit t c a) 
Dur t => Reversible (MediaUnit t c a) 

unMediaUnit :: Dur t => MediaUnit t c a -> Media c (Unit t a)Source

foldU :: Dur t => (t -> a -> b) -> (b -> b -> b) -> (b -> b -> b) -> (c -> b -> b) -> MediaUnit t c a -> Maybe bSource

fold replica for MediaUnit

fromMediaUnit :: Dur t => (c -> EventList t a -> EventList t a) -> MediaUnit t c a -> EventList t aSource

Interpretation of MediaUnit

it relies on properties of Unit (it's temporal and covertible to Maybe)

data Dur t => Unit t a Source

unit values that can happen and lasts for some time

Constructors

Unit t (Maybe a) 

Instances

Dur t => TemporalFunctor t (Unit t) 
Dur t => Sliceable t (Unit t a) 
Dur t => Stretchable t (Unit t a) 
Dur t => Temporal t (Unit t a) 
Dur t => Monad (Unit t) 
Dur t => Functor (Unit t) 
Dur t => Applicative (Unit t) 
Dur t => Construct (Unit t) 
Dur t => ToMaybe (Unit t) 
(Eq a, Dur t) => Eq (Unit t a) 
(Show a, Dur t) => Show (Unit t a) 
Dur t => Reversible (Unit t a)