| Safe Haskell | Safe |
|---|---|
| Language | Haskell98 |
Music.Theory.Time.Seq
Contents
Description
Basic temporal sequence functions.
- type Useq t a = (t, [a])
- type Dseq t a = [(t, a)]
- type Iseq t a = [(t, a)]
- type Pseq t a = [((t, t, t), a)]
- type Tseq t a = [(t, a)]
- type Wseq t a = [((t, t), a)]
- pseq_zip :: [t] -> [t] -> [t] -> [a] -> Pseq t a
- wseq_zip :: [t] -> [t] -> [a] -> Wseq t a
- seq_tspan :: Num n => (t -> n) -> (t -> n) -> [(t, a)] -> (n, n)
- tseq_tspan :: Num t => Tseq t a -> (t, t)
- wseq_tspan :: Num t => Wseq t a -> (t, t)
- wseq_start :: Num t => Wseq t a -> t
- wseq_end :: Num t => Wseq t a -> t
- dseq_dur :: Num t => Dseq t a -> t
- iseq_dur :: Num t => Iseq t a -> t
- pseq_dur :: Num t => Pseq t a -> t
- tseq_dur :: Num t => Tseq t a -> t
- wseq_dur :: Num t => Wseq t a -> t
- wseq_until :: Ord t => t -> Wseq t a -> Wseq t a
- wseq_twindow :: (Num t, Ord t) => (t, t) -> Wseq t a -> Wseq t a
- wseq_at :: (Num t, Ord t) => Wseq t a -> t -> Wseq t a
- wseq_at_window :: (Num t, Ord t) => Wseq t a -> (t, t) -> Wseq t a
- dseq_append :: Dseq t a -> Dseq t a -> Dseq t a
- iseq_append :: Iseq t a -> Iseq t a -> Iseq t a
- pseq_append :: Pseq t a -> Pseq t a -> Pseq t a
- tseq_merge :: Ord t => Tseq t a -> Tseq t a -> Tseq t a
- tseq_merge_by :: Ord t => Compare_F a -> Tseq t a -> Tseq t a -> Tseq t a
- tseq_merge_resolve :: Ord t => (a -> a -> a) -> Tseq t a -> Tseq t a -> Tseq t a
- w_compare :: Ord t => ((t, t), a) -> ((t, t), a) -> Ordering
- wseq_merge :: Ord t => Wseq t a -> Wseq t a -> Wseq t a
- wseq_merge_set :: Ord t => [Wseq t a] -> Wseq t a
- tseq_lookup_window_by :: (t -> t -> Ordering) -> Tseq t e -> t -> (Maybe (t, e), Maybe (t, e))
- tseq_lookup_active_by :: (t -> t -> Ordering) -> Tseq t e -> t -> Maybe e
- tseq_lookup_active :: Ord t => Tseq t e -> t -> Maybe e
- tseq_lookup_active_by_def :: e -> (t -> t -> Ordering) -> Tseq t e -> t -> e
- tseq_lookup_active_def :: Ord t => e -> Tseq t e -> t -> e
- data Interpolation_T
- type Lseq t a = Tseq (t, Interpolation_T) a
- lerp :: (Fractional t, Real t, Fractional e) => (t, e) -> (t, e) -> t -> e
- lseq_tmap :: (t -> t') -> Lseq t a -> Lseq t' a
- lseq_lookup :: (Fractional t, Real t, Fractional e) => (t -> t -> Ordering) -> Lseq t e -> t -> Maybe e
- lseq_lookup_err :: (Fractional t, Real t, Fractional e) => (t -> t -> Ordering) -> Lseq t e -> t -> e
- seq_tmap :: (t -> t') -> [(t, a)] -> [(t', a)]
- seq_map :: (b -> c) -> [(a, b)] -> [(a, c)]
- seq_bimap :: (t -> t') -> (e -> e') -> [(t, e)] -> [(t', e')]
- seq_tfilter :: (t -> Bool) -> [(t, a)] -> [(t, a)]
- seq_filter :: (b -> Bool) -> [(a, b)] -> [(a, b)]
- seq_find :: (a -> Bool) -> [(t, a)] -> Maybe (t, a)
- seq_map_maybe :: (p -> Maybe q) -> [(t, p)] -> [(t, q)]
- seq_cat_maybes :: [(t, Maybe q)] -> [(t, q)]
- seq_changed_by :: (a -> a -> Bool) -> [(t, a)] -> [(t, Maybe a)]
- seq_changed :: Eq a => [(t, a)] -> [(t, Maybe a)]
- wseq_tmap_st :: (t -> t) -> Wseq t a -> Wseq t a
- wseq_tmap_dur :: (t -> t) -> Wseq t a -> Wseq t a
- seq_partition :: Ord v => (a -> v) -> [(t, a)] -> [(v, [(t, a)])]
- tseq_partition :: Ord v => (a -> v) -> Tseq t a -> [(v, Tseq t a)]
- wseq_partition :: Ord v => (a -> v) -> Wseq t a -> [(v, Wseq t a)]
- coalesce_f :: (t -> t -> Bool) -> (t -> t -> t) -> [t] -> [t]
- coalesce_m :: Monoid t => (t -> t -> Bool) -> [t] -> [t]
- seq_coalesce :: Num t => (a -> a -> Bool) -> (a -> a -> a) -> [(t, a)] -> [(t, a)]
- dseq_coalesce :: Num t => (a -> a -> Bool) -> (a -> a -> a) -> Dseq t a -> Dseq t a
- dseq_coalesce' :: Num t => (a -> a -> Bool) -> Dseq t a -> Dseq t a
- iseq_coalesce :: Num t => (a -> a -> Bool) -> (a -> a -> a) -> Iseq t a -> Iseq t a
- seq_tcoalesce :: (t -> t -> Bool) -> (a -> a -> a) -> [(t, a)] -> [(t, a)]
- tseq_tcoalesce :: Eq t => (a -> a -> a) -> Tseq t a -> Tseq t a
- wseq_tcoalesce :: ((t, t) -> (t, t) -> Bool) -> (a -> a -> a) -> Wseq t a -> Wseq t a
- group_f :: (Eq t, Num t) => (t -> t -> Bool) -> [(t, a)] -> [(t, [a])]
- tseq_group :: (Eq t, Num t) => Tseq t a -> Tseq t [a]
- iseq_group :: (Eq t, Num t) => Iseq t a -> Iseq t [a]
- wseq_fill_dur :: Num t => Wseq t a -> Wseq t a
- dseq_lcm :: Dseq Rational e -> Integer
- dseq_set_whole :: [Dseq Rational e] -> [Dseq Integer e]
- tseq_latch :: Ord t => a -> Tseq t a -> [t] -> Tseq t a
- wseq_sort :: Ord t => Wseq t a -> Wseq t a
- wseq_discard_dur :: Wseq t a -> Tseq t a
- wseq_overlap_f :: (Eq e, Ord t, Num t) => (e -> e -> Bool) -> (t -> t) -> ((t, t), e) -> Wseq t e -> Maybe (Wseq t e)
- wseq_has_overlaps :: (Ord t, Num t, Eq e) => (e -> e -> Bool) -> Wseq t e -> Bool
- wseq_remove_overlaps :: (Eq e, Ord t, Num t) => (e -> e -> Bool) -> (t -> t) -> Wseq t e -> Wseq t e
- seq_unjoin :: [(t, [e])] -> [(t, e)]
- wseq_unjoin :: Wseq t [e] -> Wseq t e
- wseq_shift :: Num t => t -> Wseq t a -> Wseq t a
- wseq_append :: Num t => Wseq t a -> Wseq t a -> Wseq t a
- wseq_concat :: Num t => [Wseq t a] -> Wseq t a
- data Begin_End a
- begin_end_map :: (t -> u) -> Begin_End t -> Begin_End u
- cmp_begin_end :: Begin_End a -> Begin_End b -> Ordering
- either_to_begin_end :: Either a a -> Begin_End a
- begin_end_to_either :: Begin_End a -> Either a a
- begin_end_partition :: [Begin_End a] -> ([a], [a])
- begin_end_track :: Eq a => [a] -> Begin_End a -> [a]
- wseq_begin_end :: (Num t, Ord t) => Wseq t a -> Tseq t (Begin_End a)
- wseq_begin_end_either :: (Num t, Ord t) => Wseq t a -> Tseq t (Either a a)
- wseq_begin_end_f :: (Ord t, Num t) => (a -> b) -> (a -> b) -> Wseq t a -> Tseq t b
- tseq_begin_end_accum :: Eq a => Tseq t [Begin_End a] -> Tseq t ([a], [a], [a])
- tseq_accumulate :: Eq a => Tseq t [Begin_End a] -> Tseq t [a]
- wseq_accumulate :: (Eq a, Ord t, Num t) => Wseq t a -> Tseq t [a]
- tseq_begin_end_to_wseq :: Num t => (a -> a -> Bool) -> Tseq t (Begin_End a) -> Wseq t a
- useq_to_dseq :: Useq t a -> Dseq t a
- useq_to_wseq :: Num t => t -> Useq t a -> Wseq t a
- dseq_to_tseq :: Num t => t -> a -> Dseq t a -> Tseq t a
- dseq_to_tseq_last :: Num t => t -> Dseq t a -> Tseq t a
- pseq_to_wseq :: Num t => t -> Pseq t a -> Wseq t a
- tseq_to_dseq :: (Ord t, Num t) => a -> Tseq t a -> Dseq t a
- tseq_to_wseq :: Num t => Maybe (a -> t) -> Tseq t a -> Wseq t a
- tseq_to_iseq :: Num t => Tseq t a -> Dseq t a
- dseq_to_wseq :: Num t => t -> Dseq t a -> Wseq t a
- wseq_to_dseq :: (Num t, Ord t) => a -> Wseq t a -> Dseq t a
- dseql_to_tseql :: Num t => t -> [Dseq t a] -> (t, [Tseq t a])
- wseq_cycle' :: Num t => Wseq t a -> [Wseq t a]
- wseq_cycle :: Num t => Wseq t a -> Wseq t a
- wseq_cycle_n :: Num t => Int -> Wseq t a -> Wseq t a
- wseq_cycle_until :: (Num t, Ord t) => t -> Wseq t a -> Wseq t a
- dseq_tmap :: (t -> t') -> Dseq t a -> Dseq t' a
- pseq_tmap :: ((t, t, t) -> (t', t', t')) -> Pseq t a -> Pseq t' a
- tseq_tmap :: (t -> t') -> Dseq t a -> Dseq t' a
- tseq_bimap :: (t -> t') -> (e -> e') -> Tseq t e -> Tseq t' e'
- wseq_tmap :: ((t, t) -> (t', t')) -> Wseq t a -> Wseq t' a
- dseq_map :: (a -> b) -> Dseq t a -> Dseq t b
- pseq_map :: (a -> b) -> Pseq t a -> Pseq t b
- tseq_map :: (a -> b) -> Tseq t a -> Tseq t b
- wseq_map :: (a -> b) -> Wseq t a -> Wseq t b
- dseq_tfilter :: (t -> Bool) -> Dseq t a -> Dseq t a
- iseq_tfilter :: (t -> Bool) -> Iseq t a -> Iseq t a
- pseq_tfilter :: ((t, t, t) -> Bool) -> Pseq t a -> Pseq t a
- tseq_tfilter :: (t -> Bool) -> Tseq t a -> Tseq t a
- wseq_tfilter :: ((t, t) -> Bool) -> Wseq t a -> Wseq t a
- dseq_filter :: (a -> Bool) -> Dseq t a -> Dseq t a
- iseq_filter :: (a -> Bool) -> Iseq t a -> Iseq t a
- pseq_filter :: (a -> Bool) -> Pseq t a -> Pseq t a
- tseq_filter :: (a -> Bool) -> Tseq t a -> Tseq t a
- wseq_filter :: (a -> Bool) -> Wseq t a -> Wseq t a
- wseq_map_maybe :: (a -> Maybe b) -> Wseq t a -> Wseq t b
- wseq_cat_maybes :: Wseq t (Maybe a) -> Wseq t a
Types
type Dseq t a = [(t, a)] Source #
Duration sequence. The duration is the forward duration of the value, if it has other durations they must be encoded at a.
type Iseq t a = [(t, a)] Source #
Inter-offset sequence. The duration is the interval before the value. To indicate the duration of the final value a must have a nil (end of sequence) value.
type Pseq t a = [((t, t, t), a)] Source #
Pattern sequence. The duration is a triple of logical, sounding and forward durations.
type Tseq t a = [(t, a)] Source #
Time-point sequence. To express holes a must have an empty value. To indicate the duration of the final value a must have a nil (end of sequence) value.
Zip
Time span
seq_tspan :: Num n => (t -> n) -> (t -> n) -> [(t, a)] -> (n, n) Source #
Given functions for deriving start and end times calculate time span of sequence.
seq_tspan id id [] == (0,0) seq_tspan id id (zip [0..9] ['a'..]) == (0,9)
tseq_tspan :: Num t => Tseq t a -> (t, t) Source #
wseq_tspan :: Num t => Wseq t a -> (t, t) Source #
wseq_start :: Num t => Wseq t a -> t Source #
Start time of sequence.
wseq_start [((1,2),'a')] == 1 wseq_start [] == 0
wseq_end :: Num t => Wseq t a -> t Source #
End time of sequence.
wseq_end [((1,2),'a')] == 3 wseq_end (useq_to_wseq 0 (1,"linear")) == 6
Duration
tseq_dur :: Num t => Tseq t a -> t Source #
The interval of tseq_tspan.
tseq_dur (zip [0..] "abcde|") == 5
wseq_dur :: Num t => Wseq t a -> t Source #
The interval of wseq_tspan.
wseq_dur (zip (zip [0..] (repeat 2)) "abcde") == 6
Window
wseq_until :: Ord t => t -> Wseq t a -> Wseq t a Source #
Prefix of sequence where the start time precedes or is at the indicate time.
wseq_twindow :: (Num t, Ord t) => (t, t) -> Wseq t a -> Wseq t a Source #
Keep only elements that are entirely contained within the indicated temporal window, which is inclusive at the left & right edges, ie. [t0,t1]. Halts processing at end of window.
let r = [((5,1),'e'),((6,1),'f'),((7,1),'g'),((8,1),'h')] in wseq_twindow (5,9) (zip (zip [1..] (repeat 1)) ['a'..]) == r
wseq_twindow (1,2) [((1,1),'a'),((1,2),'b')] == [((1,1),'a')]
wseq_at :: (Num t, Ord t) => Wseq t a -> t -> Wseq t a Source #
Select nodes that are active at indicated time, comparison is inclusive at left and exclusive at right. Halts processing at end of window.
let sq = [((1,1),'a'),((1,2),'b')] in map (wseq_at sq) [1,2] == [sq,[((1,2),'b')]]
wseq_at (zip (zip [1..] (repeat 1)) ['a'..]) 3 == [((3,1),'c')]
wseq_at_window :: (Num t, Ord t) => Wseq t a -> (t, t) -> Wseq t a Source #
Select nodes that are active within the indicated window, comparison is inclusive at left and exclusive at right. Halts processing at end of window.
let sq = [((0,2),'a'),((0,4),'b'),((2,4),'c')] in wseq_at_window sq (1,3) == sq
wseq_at_window (zip (zip [1..] (repeat 1)) ['a'..]) (3,4) == [((3,1),'c'),((4,1),'d')]
Append
Merge
tseq_merge_by :: Ord t => Compare_F a -> Tseq t a -> Tseq t a -> Tseq t a Source #
Merge, where times are equal compare values.
tseq_merge_resolve :: Ord t => (a -> a -> a) -> Tseq t a -> Tseq t a -> Tseq t a Source #
Merge, where times are equal apply f to form a single value.
let {p = zip [1,3,5] "abc"
;q = zip [1,2,3] "ABC"
;left_r = [(1,'a'),(2,'B'),(3,'b'),(5,'c')]
;right_r = [(1,'A'),(2,'B'),(3,'C'),(5,'c')]}
in tseq_merge_resolve (\x _ -> x) p q == left_r &&
tseq_merge_resolve (\_ x -> x) p q == right_rw_compare :: Ord t => ((t, t), a) -> ((t, t), a) -> Ordering Source #
Compare first by start time, then by duration.
wseq_merge_set :: Ord t => [Wseq t a] -> Wseq t a Source #
Merge set considering both start times & durations.
Lookup
tseq_lookup_window_by :: (t -> t -> Ordering) -> Tseq t e -> t -> (Maybe (t, e), Maybe (t, e)) Source #
Locate nodes to the left and right of indicated time.
tseq_lookup_active_by_def :: e -> (t -> t -> Ordering) -> Tseq t e -> t -> e Source #
tseq_lookup_active_def :: Ord t => e -> Tseq t e -> t -> e Source #
Lseq
data Interpolation_T Source #
Instances
type Lseq t a = Tseq (t, Interpolation_T) a Source #
Variant of Tseq where nodes have an Intepolation_T value.
lerp :: (Fractional t, Real t, Fractional e) => (t, e) -> (t, e) -> t -> e Source #
Linear interpolation.
lseq_lookup :: (Fractional t, Real t, Fractional e) => (t -> t -> Ordering) -> Lseq t e -> t -> Maybe e Source #
lseq_lookup_err :: (Fractional t, Real t, Fractional e) => (t -> t -> Ordering) -> Lseq t e -> t -> e Source #
erroring variant.
Map, Filter, Find
seq_tfilter :: (t -> Bool) -> [(t, a)] -> [(t, a)] Source #
seq_filter :: (b -> Bool) -> [(a, b)] -> [(a, b)] Source #
Maybe
seq_map_maybe :: (p -> Maybe q) -> [(t, p)] -> [(t, q)] Source #
mapMaybe variant.
seq_cat_maybes :: [(t, Maybe q)] -> [(t, q)] Source #
Variant of catMaybes.
seq_changed_by :: (a -> a -> Bool) -> [(t, a)] -> [(t, Maybe a)] Source #
If value is unchanged, according to f, replace with Nothing.
let r = [(1,'s'),(2,'t'),(4,'r'),(6,'i'),(7,'n'),(9,'g')] in seq_cat_maybes (seq_changed_by (==) (zip [1..] "sttrrinng")) == r
seq_changed :: Eq a => [(t, a)] -> [(t, Maybe a)] Source #
Specialised temporal maps.
Partition
seq_partition :: Ord v => (a -> v) -> [(t, a)] -> [(v, [(t, a)])] Source #
Given a function that determines a voice for a value, partition a sequence into voices.
tseq_partition :: Ord v => (a -> v) -> Tseq t a -> [(v, Tseq t a)] Source #
Type specialised seq_partition.
let {p = zip [0,1,3,5] (zip (repeat 0) "abcd")
;q = zip [2,4,6,7] (zip (repeat 1) "ABCD")
;sq = tseq_merge p q}
in tseq_partition fst sq == [(0,p),(1,q)]Coalesce
coalesce_f :: (t -> t -> Bool) -> (t -> t -> t) -> [t] -> [t] Source #
Given a decision predicate and a join function, recursively join adjacent elements.
coalesce_f undefined undefined [] == [] coalesce_f (==) const "abbcccbba" == "abcba" coalesce_f (==) (+) [1,2,2,3,3,3] == [1,4,6,3]
coalesce_m :: Monoid t => (t -> t -> Bool) -> [t] -> [t] Source #
coalesce_f using mappend for the join function.
seq_coalesce :: Num t => (a -> a -> Bool) -> (a -> a -> a) -> [(t, a)] -> [(t, a)] Source #
Form of coalesce_f where the decision predicate is on the
element, and a join function sums the times.
let r = [(1,'a'),(2,'b'),(3,'c'),(2,'d'),(1,'e')] in seq_coalesce (==) const (useq_to_dseq (1,"abbcccdde")) == r
dseq_coalesce' :: Num t => (a -> a -> Bool) -> Dseq t a -> Dseq t a Source #
Given equality predicate, simplify sequence by summing
durations of adjacent equal elements. This is a special case of
dseq_coalesce where the join function is const. The
implementation is simpler and non-recursive.
let {d = useq_to_dseq (1,"abbcccdde")
;r = dseq_coalesce (==) const d}
in dseq_coalesce' (==) d == rT-coalesce
seq_tcoalesce :: (t -> t -> Bool) -> (a -> a -> a) -> [(t, a)] -> [(t, a)] Source #
Group
tseq_group :: (Eq t, Num t) => Tseq t a -> Tseq t [a] Source #
Group values at equal time points.
let r = [(0,"a"),(1,"bc"),(2,"de"),(3,"f")] in tseq_group (zip [0,1,1,2,2,3] ['a'..]) == r
tseq_group [(1,'a'),(1,'b')] == [(1,"ab")] tseq_group [(1,'a'),(2,'b'),(2,'c')] == [(1,"a"),(2,"bc")]
iseq_group :: (Eq t, Num t) => Iseq t a -> Iseq t [a] Source #
Group values where the inter-offset time is 0 to the left.
let r = [(0,"a"),(1,"bcd"),(1,"ef")] in iseq_group (zip [0,1,0,0,1,0] ['a'..]) == r
Fill
wseq_fill_dur :: Num t => Wseq t a -> Wseq t a Source #
Set durations so that there are no gaps or overlaps.
let r = wseq_zip [0,3,5] [3,2,1] "abc" in wseq_fill_dur (wseq_zip [0,3,5] [2,1,1] "abc") == r
Dseq
dseq_set_whole :: [Dseq Rational e] -> [Dseq Integer e] Source #
Scale by lcm so that all durations are integral.
Tseq
tseq_latch :: Ord t => a -> Tseq t a -> [t] -> Tseq t a Source #
Given a a default value, a Tseq sq and a list of time-points
t, generate a Tseq that is a union of the timepoints at sq and
t where times in t not at sq are given the current value,
or def if there is no value.
tseq_latch 'a' [(2,'b'),(4,'c')] [1..5] == zip [1..5] "abbcc"
Wseq
wseq_overlap_f :: (Eq e, Ord t, Num t) => (e -> e -> Bool) -> (t -> t) -> ((t, t), e) -> Wseq t e -> Maybe (Wseq t e) Source #
wseq_has_overlaps :: (Ord t, Num t, Eq e) => (e -> e -> Bool) -> Wseq t e -> Bool Source #
Determine if sequence has overlapping equal nodes.
wseq_remove_overlaps :: (Eq e, Ord t, Num t) => (e -> e -> Bool) -> (t -> t) -> Wseq t e -> Wseq t e Source #
Edit durations to ensure that nodes don't overlap. If equal nodes begin simultaneously delete the shorter node. If a node extends into a later node shorten the initial duration (apply dur_fn to iot).
let sq = [((0,1),'a'),((0,5),'a'),((1,5),'a'),((3,1),'a')] let r = [((0,1),'a'),((1,2),'a'),((3,1),'a')] wseq_has_overlaps (==) sq == True wseq_remove_overlaps (==) id sq == r wseq_has_overlaps (==) (wseq_remove_overlaps (==) id sq) == False
seq_unjoin :: [(t, [e])] -> [(t, e)] Source #
Unjoin elements (assign equal time stamps to all elements).
wseq_unjoin :: Wseq t [e] -> Wseq t e Source #
Type specialised.
wseq_shift :: Num t => t -> Wseq t a -> Wseq t a Source #
Shift (displace) onset times by i.
wseq_shift 3 [((1,2),'a')] == [((4,2),'a')]
wseq_append :: Num t => Wseq t a -> Wseq t a -> Wseq t a Source #
Shift q to end of p and append.
wseq_append [((1,2),'a')] [((1,2),'b')] == [((1,2),'a'),((4,2),'b')]
wseq_concat :: Num t => [Wseq t a] -> Wseq t a Source #
wseq_concat [[((1,2),'a')],[((1,2),'b')]] == [((1,2),'a'),((4,2),'b')]
Begin/End
Container to mark the begin and end of a value.
begin_end_map :: (t -> u) -> Begin_End t -> Begin_End u Source #
Functor instance.
either_to_begin_end :: Either a a -> Begin_End a Source #
Translate container types.
begin_end_to_either :: Begin_End a -> Either a a Source #
Translate container types.
begin_end_partition :: [Begin_End a] -> ([a], [a]) Source #
begin_end_track :: Eq a => [a] -> Begin_End a -> [a] Source #
Add or delete element from accumulated state.
wseq_begin_end :: (Num t, Ord t) => Wseq t a -> Tseq t (Begin_End a) Source #
Convert Wseq to Tseq transforming elements to Begin_End.
When merging, end elements precede begin elements at equal times.
let {sq = [((0,5),'a'),((2,2),'b')]
;r = [(0,Begin 'a'),(2,Begin 'b'),(4,End 'b'),(5,End 'a')]}
in wseq_begin_end sq == rlet {sq = [((0,1),'a'),((1,1),'b'),((2,1),'c')]
;r = [(0,Begin 'a'),(1,End 'a')
,(1,Begin 'b'),(2,End 'b')
,(2,Begin 'c'),(3,End 'c')]}
in wseq_begin_end sq == rwseq_begin_end_f :: (Ord t, Num t) => (a -> b) -> (a -> b) -> Wseq t a -> Tseq t b Source #
Variant that applies begin and end functions to nodes.
let {sq = [((0,5),'a'),((2,2),'b')]
;r = [(0,'A'),(2,'B'),(4,'b'),(5,'a')]}
in wseq_begin_end_f Data.Char.toUpper id sq == rtseq_begin_end_accum :: Eq a => Tseq t [Begin_End a] -> Tseq t ([a], [a], [a]) Source #
Result for each time-point the triple (begin-list,end-list,hold-list). The elements of the end-list have been deleted from the hold list.
wseq_accumulate :: (Eq a, Ord t, Num t) => Wseq t a -> Tseq t [a] Source #
The transition sequence of active elements.
let w = [((0,3),'a'),((1,2),'b'),((2,1),'c'),((3,3),'d')] wseq_accumulate w == [(0,"a"),(1,"ba"),(2,"cba"),(3,"d"),(6,"")]
tseq_begin_end_to_wseq :: Num t => (a -> a -> Bool) -> Tseq t (Begin_End a) -> Wseq t a Source #
Inverse of wseq_begin_end given a predicate function for locating
the end node of a begin node.
let {sq = [(0,Begin 'a'),(2,Begin 'b'),(4,End 'b'),(5,End 'a')]
;r = [((0,5),'a'),((2,2),'b')]}
in tseq_begin_end_to_wseq (==) sq == rInterop
useq_to_dseq :: Useq t a -> Dseq t a Source #
dseq_to_tseq :: Num t => t -> a -> Dseq t a -> Tseq t a Source #
The conversion requires a start time and a nil value used as an eof marker. Productive given indefinite input sequence.
let r = zip [0,1,3,6,8,9] "abcde|" in dseq_to_tseq 0 '|' (zip [1,2,3,2,1] "abcde") == r
let {d = zip [1,2,3,2,1] "abcde"
;r = zip [0,1,3,6,8,9,10] "abcdeab"}
in take 7 (dseq_to_tseq 0 undefined (cycle d)) == rdseq_to_tseq_last :: Num t => t -> Dseq t a -> Tseq t a Source #
Variant where the nil value is taken from the last element of the sequence.
let r = zip [0,1,3,6,8,9] "abcdee" in dseq_to_tseq_last 0 (zip [1,2,3,2,1] "abcde") == r
pseq_to_wseq :: Num t => t -> Pseq t a -> Wseq t a Source #
The conversion requires a start time and does not consult the logical duration.
let p = pseq_zip (repeat undefined) (cycle [1,2]) (cycle [1,1,2]) "abcdef" in pseq_to_wseq 0 p == wseq_zip [0,1,2,4,5,6] (cycle [1,2]) "abcdef"
tseq_to_dseq :: (Ord t, Num t) => a -> Tseq t a -> Dseq t a Source #
The last element of Tseq is required to be an eof marker that
has no duration and is not represented in the Dseq. A nil
value is required in case the Tseq does not begin at 0.
let r = zip [1,2,3,2,1] "abcde" in tseq_to_dseq undefined (zip [0,1,3,6,8,9] "abcde|") == r
let r = zip [1,2,3,2,1] "-abcd" in tseq_to_dseq '-' (zip [1,3,6,8,9] "abcd|") == r
tseq_to_wseq :: Num t => Maybe (a -> t) -> Tseq t a -> Wseq t a Source #
The last element of Tseq is required to be an eof marker that
has no duration and is not represented in the Wseq. The duration
of each value is either derived from the value, if an dur
function is given, or else the inter-offset time.
let r = wseq_zip [0,1,3,6,8] [1,2,3,2,1] "abcde" in tseq_to_wseq Nothing (zip [0,1,3,6,8,9] "abcde|") == r
let r = wseq_zip [0,1,3,6,8] (map fromEnum "abcde") "abcde" in tseq_to_wseq (Just fromEnum) (zip [0,1,3,6,8,9] "abcde|") == r
dseq_to_wseq :: Num t => t -> Dseq t a -> Wseq t a Source #
Requires start time.
let r = zip (zip [0,1,3,6,8,9] [1,2,3,2,1]) "abcde" in dseq_to_wseq 0 (zip [1,2,3,2,1] "abcde") == r
wseq_to_dseq :: (Num t, Ord t) => a -> Wseq t a -> Dseq t a Source #
Inverse of dseq_to_wseq. The empty value is used to fill
holes in Wseq. If values overlap at Wseq durations are
truncated.
let w = wseq_zip [0,1,3,6,8,9] [1,2,3,2,1] "abcde" in wseq_to_dseq '-' w == zip [1,2,3,2,1] "abcde"
let w = wseq_zip [3,10] [6,2] "ab" in wseq_to_dseq '-' w == zip [3,6,1,2] "-a-b"
let w = wseq_zip [0,1] [2,2] "ab" in wseq_to_dseq '-' w == zip [1,2] "ab"
let w = wseq_zip [0,0,0] [2,2,2] "abc" in wseq_to_dseq '-' w == zip [0,0,2] "abc"
Measures
Cycle
wseq_cycle :: Num t => Wseq t a -> Wseq t a Source #
Only finite Wseq can be cycled, the resulting Wseq is infinite.
take 5 (wseq_cycle [((0,1),'a'),((3,3),'b')])
wseq_cycle_n :: Num t => Int -> Wseq t a -> Wseq t a Source #
Variant cycling only n times.
wseq_cycle_n 3 [((0,1),'a'),((3,3),'b')]
wseq_cycle_until :: (Num t, Ord t) => t -> Wseq t a -> Wseq t a Source #
wseq_until of wseq_cycle.
Type specialised map
tseq_bimap :: (t -> t') -> (e -> e') -> Tseq t e -> Tseq t' e' Source #