Karya, built on 2023-08-29T07:47:28 (patch 7a412d5d6ba4968ca4155ef276a062ccdeb9109a)
Safe HaskellSafe-Inferred

Util.Segment

Description

The Signal type and functions.

Synopsis

Documentation

data Signal v Source #

A signal modeled as segments. Presumably the segments are linear, but since you pass your own Interpolate, nothing in this module enforces that, though there are some transformations that are only valid for linear segments.

A signal has no value before its first sample, and maintains a constant value of the last sample forever. There is an implicit discontinuity to the first sample, so if x is the first sample, then [(x, y), ..] is implicitly [(x, Nothing), (x, y), ...]. NumSignal uses 0 for not set, so unless the first y is also 0 it becomes [(x, 0), (x, y), ..].

This comes with a built-in X offset, so translation is cheap, via shift.

Each X should be >= the previous X, and there shouldn't be more than two equal Xs in a row. The first ensures that binary search works, and the second insures that I don't try to interpolate a zero length segment. Construction via from_samples should establish them, and transformations should maintain them.

However, a few functions in here can break them, e.g. map_x and invert, and I think trying to fix them would be expensive. So be careful with those. Functions should be robust against zero length segments, but if you break ordering you're out of luck.

If the y value doesn't have an Eq instance, there's no way to filter out redundant segments like [(0, 1), (1, 1), (2, 1)]. Functions specialized to NumSignal may make some effort to do that, but only if it seems worth it.

Instances

Instances details
Show v => Show (Signal v) Source # 
Instance details

Defined in Util.Segment

Methods

showsPrec :: Int -> Signal v -> ShowS #

show :: Signal v -> String #

showList :: [Signal v] -> ShowS #

DeepSeq.NFData v => DeepSeq.NFData (Signal v) Source # 
Instance details

Defined in Util.Segment

Methods

rnf :: Signal v -> () #

Eq v => Eq (Signal v) Source # 
Instance details

Defined in Util.Segment

Methods

(==) :: Signal v -> Signal v -> Bool #

(/=) :: Signal v -> Signal v -> Bool #

Pretty.Pretty v => Pretty.Pretty (Signal v) Source # 
Instance details

Defined in Util.Segment

Serialize.Serialize v => Serialize.Serialize (Signal v) Source # 
Instance details

Defined in Util.Segment

type SignalS v y = Signal (v (Sample y)) Source #

type Interpolate y = Sample y -> Sample y -> X -> y Source #

data Segment y Source #

Constructors

Segment 

Fields

Instances

Instances details
Show y => Show (Segment y) Source # 
Instance details

Defined in Util.Segment

Methods

showsPrec :: Int -> Segment y -> ShowS #

show :: Segment y -> String #

showList :: [Segment y] -> ShowS #

Eq y => Eq (Segment y) Source # 
Instance details

Defined in Util.Segment

Methods

(==) :: Segment y -> Segment y -> Bool #

(/=) :: Segment y -> Segment y -> Bool #

Pretty.Pretty y => Pretty.Pretty (Segment y) Source # 
Instance details

Defined in Util.Segment

data Sample y Source #

Constructors

Sample 

Fields

Instances

Instances details
Storable (Sample Double) Source # 
Instance details

Defined in Util.TimeVectorStorable

Show y => Show (Sample y) Source # 
Instance details

Defined in Util.TimeVectorStorable

Methods

showsPrec :: Int -> Sample y -> ShowS #

show :: Sample y -> String #

showList :: [Sample y] -> ShowS #

CStorable (Sample Double) Source # 
Instance details

Defined in Util.TimeVectorStorable

Eq y => Eq (Sample y) Source # 
Instance details

Defined in Util.TimeVectorStorable

Methods

(==) :: Sample y -> Sample y -> Bool #

(/=) :: Sample y -> Sample y -> Bool #

Pretty.Pretty y => Pretty.Pretty (Sample y) Source # 
Instance details

Defined in Util.TimeVector

Serialize.Serialize y => Serialize.Serialize (Sample y) Source # 
Instance details

Defined in Util.TimeVectorStorable

FromJSON (Sample Double) Source # 
Instance details

Defined in Util.TimeVectorStorable

ToJSON (Sample Double) Source # 
Instance details

Defined in Util.TimeVectorStorable

construct / destruct

empty :: V.Vector v a => Signal (v a) Source #

constant :: V.Vector v (Sample y) => y -> SignalS v y Source #

constant_val_num :: X -> NumSignal -> Maybe.Maybe Y Source #

constant_val for NumSignals can be more clever, because it can compare Ys. Also NumSignals are implicitly 0 before the first sample.

all_y :: (Y -> Bool) -> NumSignal -> Bool Source #

beginning :: RealTime.RealTime Source #

Use this as the stand-in for "since the beginning of time."

to_vector :: V.Vector v (Sample y) => SignalS v y -> v (Sample y) Source #

from_samples :: V.Vector v (Sample y) => [Sample y] -> SignalS v y Source #

The final sample extends for "all time". However, there's no value before the first sample. The reason is that I'd have to have a zero value for y, and there isn't really an appropriate one for pitch.

TODO I could simplify straight lines, but then I'd need Eq on y. Maybe do that separately for NumSignal.

from_pairs :: V.Vector v (Sample y) => [(X, y)] -> SignalS v y Source #

to_pairs :: V.Vector v (Sample y) => SignalS v y -> [(X, y)] Source #

to_pairs_desc :: V.Vector v (Sample y) => SignalS v y -> [(X, y)] Source #

simplify :: (Eq x, Eq y) => [(x, y)] -> [(x, y)] Source #

Simplify away redundant samples.

unfoldr :: V.Vector v (Sample y) => (state -> Maybe.Maybe ((X, y), state)) -> state -> SignalS v y Source #

with_ptr :: Storable a => Signal (Vector.Storable.Vector a) -> (X -> Ptr a -> Int -> IO b) -> IO b Source #

Get a Ptr to the vector. This is Vector.Storable.unsafeWith.

query

null :: V.Vector v (Sample y) => SignalS v y -> Bool Source #

at :: V.Vector v (Sample y) => Interpolate y -> SignalS v y -> X -> Maybe.Maybe y Source #

The arguments may seem backwards, but I've always done it this way, and it seems to be more convenient in practice.

at_negative :: V.Vector v (Sample y) => Interpolate y -> SignalS v y -> X -> Maybe.Maybe y Source #

Like at, but if the x matches a discontinuity, take the value before instead of after.

head :: V.Vector v (Sample y) => SignalS v y -> Maybe.Maybe (X, y) Source #

last :: V.Vector v (Sample y) => SignalS v y -> Maybe.Maybe (X, y) Source #

maximum :: (V.Vector v (Sample a), Ord a) => SignalS v a -> Maybe.Maybe a Source #

minimum :: (V.Vector v (Sample a), Ord a) => SignalS v a -> Maybe.Maybe a Source #

find :: V.Vector v (Sample y) => (X -> y -> Bool) -> Signal (v (Sample y)) -> Maybe.Maybe (X, y) Source #

concat

concat Source #

Arguments

:: V.Vector v (Sample y) 
=> Maybe.Maybe (y -> y -> Bool)

signals with Eq y can drop some redundant samples

-> Interpolate y 
-> [SignalS v y] 
-> SignalS v y 

Concatenate signals, where signals to the right replace the ones to the left where they overlap.

prepend :: V.Vector v (Sample y) => Maybe.Maybe (y -> y -> Bool) -> Interpolate y -> SignalS v y -> SignalS v y -> SignalS v y Source #

With concat, each signal start clips the signal to its left. This is the other way around, the final sample in the first signal is taken as its end, and it replaces the start of the second signal.

slice

drop_after :: V.Vector v (Sample y) => X -> SignalS v y -> SignalS v y Source #

Drop the segments after the given time. The last segment may overlap it.

clip_after :: V.Vector v (Sample y) => Interpolate y -> X -> SignalS v y -> SignalS v y Source #

This is like drop_after, but meant to clip the signal directly on x, rather than at the first sample >=x. This means I might have to insert a new sample, which means copying the signal. This is intended to be a "drop at and after", but since signals extend infinitely to the right, I can only go up to x. TODO maybe signals should go to Nothing >= the last sample?

If the signal has only a point exactly at x, then return the empty signal. This is because the first sample is effectively a transition from Nothing, or 0.

drop_before :: V.Vector v (Sample y) => X -> SignalS v y -> SignalS v y Source #

Drop the segments before the given time. The first segment will start at or before the given time.

clip_before :: V.Vector v (Sample y) => Interpolate y -> X -> SignalS v y -> SignalS v y Source #

Like drop_before, but ensure that the signal starts exactly at the given time by splitting a segment that crosses it.

transform

shift :: X -> Signal v -> Signal v Source #

Shift the signal in time.

map_y :: X -> (Y -> Y) -> NumSignal -> NumSignal Source #

Map Ys. This resamples the signal, so it's valid for a nonlinear function.

map_y_linear :: V.Vector v (Sample y) => (y -> y) -> SignalS v y -> SignalS v y Source #

Map Ys. Only valid if the function is linear.

map_x :: V.Vector v (Sample y) => (X -> X) -> SignalS v y -> SignalS v y Source #

Map Xs. The slopes will definitely change unless the function is adding a constant, but presumably that's what you want.

TODO this can break Signal invariants.

transform_samples :: V.Vector v (Sample y) => ([Sample y] -> [Sample y]) -> SignalS v y -> SignalS v y Source #

map_err :: V.Vector v (Sample y) => (Sample y -> Either err (Sample y)) -> SignalS v y -> (SignalS v y, [err]) Source #

hacks

drop_discontinuity_at :: V.Vector v (Sample y) => X -> SignalS v y -> SignalS v y Source #

Drop a x1==x2 discontinuity at the given time, if there is one. Used for Block.trim_controls, which is a terrible hack that I'm trying to get rid of.

Boxed

NumSignal

invert :: NumSignal -> NumSignal Source #

Swap X and Y. Y must be non-decreasing or this will break Signal invariants.

integrate :: X -> NumSignal -> NumSignal Source #

Integrate the signal.

Since the output will have more samples than the input, this needs a sampling rate. The sampling rate determines the resolution of the tempo track. So it can probably be fairly low resolution before having a noticeable impact.

resample

linear_operator :: (Y -> Y -> Y) -> NumSignal -> NumSignal -> NumSignal Source #

Combine two vectors with the given function. The signals are resampled to have coincident samples, assuming linear interpolation. This only works for linear functions, so the result can also be represented with linear segments.

resample_num :: [X] -> [Sample Y] -> [Y] Source #

resample_maybe :: Interpolate y -> [X] -> [Sample y] -> [Maybe.Maybe y] Source #

This is the same as resample, only for ys without a zero.

sample_xs :: [[X]] -> [X] Source #

The output has the union of the Xs in the inputs, except where they match exactly. Discontinuities should get two Xs. This is the list version of sample_xs2.

piecewise constant