Safe Haskell | None |
---|---|
Language | Haskell98 |
- type Trace t a = [(t, a)]
- trace_start_time :: Num t => Trace t a -> t
- trace_end_time :: Num t => Trace t a -> t
- type Window t = (t, t)
- trace_window :: Num t => Trace t a -> Window t
- type Lerp_F t a b = t -> a -> a -> b
- type Time = R
- trace_load_sf :: Maybe Int -> FilePath -> IO (Trace Time [R])
- trace_load_sf2 :: FilePath -> IO (Trace Time (R, R))
- trace_load_sf_dir :: Maybe Int -> String -> IO [Trace Time [R]]
- trace_load_sf2_dir :: String -> IO [Trace Time (R, R)]
- trace_map_t :: (t -> t') -> Trace t a -> Trace t' a
- trace_map :: (a -> b) -> Trace t a -> Trace t b
- trace_locate :: (Ord t, Fractional t) => Trace t a -> t -> Either String (((t, a), (t, a)), Trace t a)
- trace_neighbours :: (Ord t, Fractional t) => Trace t a -> t -> Maybe ((t, a), (t, a))
- trace_neighbours_err :: (Fractional t, Ord t) => Trace t a -> t -> ((t, a), (t, a))
- trace_lerp :: Fractional t => Lerp_F t a b -> t -> (t, a) -> (t, a) -> (t, b)
- trace_lookup :: (Ord t, Fractional t) => Lerp_F t a b -> Trace t a -> t -> Maybe (t, b)
- trace_lookup_def :: (Ord t, Fractional t) => b -> Lerp_F t a b -> Trace t a -> t -> (t, b)
- trace_lookup_err :: (Ord t, Fractional t) => Lerp_F t a b -> Trace t a -> t -> (t, b)
- trace_lookup_seq_asc :: (Ord t, Fractional t) => Lerp_F t a b -> Trace t a -> [t] -> Trace t b
- trace_normalise_t :: Fractional t => Trace t a -> Trace t a
- trace_linearise :: (Ord t, Fractional t) => Int -> Lerp_F t a b -> Trace t a -> Window t -> Trace t b
- trace_linearise_w :: (Ord t, Fractional t) => Int -> Lerp_F t a b -> Trace t a -> Trace t b
- trace_table :: (Ord t, Fractional t) => Int -> Lerp_F t a b -> Trace t a -> [b]
- trace_rescale :: (Eq t, Ord t, Fractional t) => Lerp_F t a b -> Trace t a -> Int -> Trace t b
- trace_expand :: Fractional t => Lerp_F t a a -> Trace t a -> Trace t a
- trace_expand_n :: (Fractional t, Integral n) => Lerp_F t a a -> Trace t a -> n -> Trace t a
- lerpn :: Num a => a -> a -> a -> a
- lerpn2 :: Num n => n -> (n, n) -> (n, n) -> (n, n)
- lerp_pw :: Lerp_F t a b -> t -> [a] -> [a] -> [b]
- lerpd :: Num c => c -> [c] -> [c] -> [c]
- ls_with_distance :: (Eq t, Floating t) => Ls t -> Trace t (Pt t)
- iota' :: (Eq n, Num n, Eq m, Num m) => n -> n -> n -> m -> [n]
- iota :: (Integral m, Eq n, Fractional n) => n -> n -> m -> [n]
- interleave2 :: ([t], [t]) -> [t]
- deinterleave2 :: [a] -> ([a], [a])
- trace2_plot_3d :: [Trace R (R, R)] -> IO ()
- trace2_plot_2d :: [Trace R (R, R)] -> IO ()
- trace2_plot_tbl :: [Trace R (R, R)] -> IO ()
Documentation
type Trace t a = [(t, a)] Source
Traces are sequences Ord t => [(t,a)]
where t is ascending.
Ordinarily t is a time-point, and traces are temporal.
However t may be, for instance, distance traversed so that line segments (sequences of cartesian points) can be transformed into Traces by associating each point with the distance along the line.
If there is an interpolation function (linear or otherwise) for the type a we can lookup a value for any index t in the window of the trace.
Traces can be both more accurate and more compact than sampled data streams.
Break-point envelopes are Traces where a is a scalar
(interpolation-type,value)
.
Traces are normal if t0 is >= 0 and tn is <= 1.
Traces are strictly normal if t0 == 0 and tn == 1.
trace_start_time :: Num t => Trace t a -> t Source
Start time of trace, or zero for null trace.
trace_end_time :: Num t => Trace t a -> t Source
End time of trace, or zero for null trace.
A trace window is a pait (t0,t1) indicating the begin and end time points.
trace_window :: Num t => Trace t a -> Window t Source
Start and end times of trace, or (0,0) for null trace.
IO
trace_load_sf :: Maybe Int -> FilePath -> IO (Trace Time [R]) Source
Load real valued trace stored as a sound file.
The temporal data is in the first channel, subsequent channels are associated data points. If set nc is set it requires the file have precisely the indicated number of _data_ channels, ie. nc does not include the _temporal_ channel.
trace_load_sf2 :: FilePath -> IO (Trace Time (R, R)) Source
Variant for loading two-channel trace file.
trace_load_sf_dir :: Maybe Int -> String -> IO [Trace Time [R]] Source
Variant for set of traces given by glob
pattern'.
Functor
trace_map_t :: (t -> t') -> Trace t a -> Trace t' a Source
Map over trace times.
Lookup
trace_locate :: (Ord t, Fractional t) => Trace t a -> t -> Either String (((t, a), (t, a)), Trace t a) Source
Trace nodes that bracket time t, and trace starting from left neighbour.
map (trace_locate (zip [0..9] ['a'..])) [-1,3.5,10]
trace_neighbours :: (Ord t, Fractional t) => Trace t a -> t -> Maybe ((t, a), (t, a)) Source
fst
of trace_locate
trace_neighbours (zip [0..9] ['a'..]) 3.5 == Just ((3.0,'d'),(4.0,'e'))
trace_neighbours_err :: (Fractional t, Ord t) => Trace t a -> t -> ((t, a), (t, a)) Source
trace_lerp :: Fractional t => Lerp_F t a b -> t -> (t, a) -> (t, a) -> (t, b) Source
Interpolate between to trace points using given interpolation function.
trace_lookup :: (Ord t, Fractional t) => Lerp_F t a b -> Trace t a -> t -> Maybe (t, b) Source
Linear interpolating lookup, ie. trace_lerp
of trace_neighbours
.
t <- trace_load_sf2_dir "/home/rohan/sw/hsc3-data/help/au/*.txy.au" map (\z -> trace_lookup lerpn2 z 0.5) t
trace_lookup_def :: (Ord t, Fractional t) => b -> Lerp_F t a b -> Trace t a -> t -> (t, b) Source
trace_lookup
with default value.
trace_lookup_err :: (Ord t, Fractional t) => Lerp_F t a b -> Trace t a -> t -> (t, b) Source
fromJust
of trace_lookup
.
trace_lookup_seq_asc :: (Ord t, Fractional t) => Lerp_F t a b -> Trace t a -> [t] -> Trace t b Source
Operate
trace_normalise_t :: Fractional t => Trace t a -> Trace t a Source
Normalise so that trace_window
is (0,1).
let r = [(0,'a'),(0.2,'b'),(1,'c')] in trace_normalise_t [(0,'a'),(1,'b'),(5,'c')] == r
trace_linearise :: (Ord t, Fractional t) => Int -> Lerp_F t a b -> Trace t a -> Window t -> Trace t b Source
Transform trace to an n-point linear form (time-points are
equi-distant) over indicated Window
(which must be ascending, ie
t0 < t1).
trace_linearise_w :: (Ord t, Fractional t) => Int -> Lerp_F t a b -> Trace t a -> Trace t b Source
Variant where the range is derived implicity from input trace
(trace_window
).
t <- trace_load_sf2_dir "/home/rohan/sw/hsc3-data/help/au/*.txy.au" plotCoord (map (trace_linearise_w 1024 lerpn . trace_map fst) t) plotCoord (map (trace_map fst) t) trace2_plot_tbl t
trace_table :: (Ord t, Fractional t) => Int -> Lerp_F t a b -> Trace t a -> [b] Source
Values only of trace_linearise_w
.
plotTable (map (trace_table 1024 lerpn . trace_map fst) t)
trace_rescale :: (Eq t, Ord t, Fractional t) => Lerp_F t a b -> Trace t a -> Int -> Trace t b Source
Variant of trace_linearize
assuming t is normalised.
trace_rescale lerpd [(0,[1]),(2,[2])] 3 == [(0,[1]),(0.5,[1.25]),(1,[1.5])]
trace_expand :: Fractional t => Lerp_F t a a -> Trace t a -> Trace t a Source
Interpolate maintaining temporal shape, divide each step in half.
let r = [(0,[0]),(0.5,[0.5]),(1,[1]),(2.5,[2.5]),(4,[4])] in trace_expand lerpd [(0,[0]),(1,[1]),(4,[4])] == r
trace2_plot_3d (map (trace_expand lerpn2) t)
trace_expand_n :: (Fractional t, Integral n) => Lerp_F t a a -> Trace t a -> n -> Trace t a Source
Recursive expansion
length (trace_expand_n lerpd [(0,[0]),(1,[1]),(4,[4])] 3) == 17
Interpolation
lerpn :: Num a => a -> a -> a -> a Source
Linear interpolation.
zipWith (lerpn 0.25) [4,5] [6,9] == [4.5,6.0]
lerpn2 :: Num n => n -> (n, n) -> (n, n) -> (n, n) Source
Variant at uniform 2-tuple.
lerpn2 0.25 (4,5) (6,9) == (4.5,6.0)
lerp_pw :: Lerp_F t a b -> t -> [a] -> [a] -> [b] Source
Pointwise linear interpolation at lists.
lerp_pw lerpn 0.25 [4,5] [6,9] == [4.5,6]
Geometry
List
iota' :: (Eq n, Num n, Eq m, Num m) => n -> n -> n -> m -> [n] Source
Generic iota function (name courtesy scheme language) with explicit increment. The last value is the given end-point regardless of accumulated errors.
iota' 0 1 0.25 5 == [0,0.25,0.5,0.75,1]
iota :: (Integral m, Eq n, Fractional n) => n -> n -> m -> [n] Source
Fractional iota function with implicit increment.
iota 0 1 5 == [0,0.25,0.5,0.75,1]
interleave2 :: ([t], [t]) -> [t] Source
Alternate elements of two lists.
interleave2 ("one","two") == "otnweo" interleave2 ("long","short") == "lsohnogrt"
deinterleave2 :: [a] -> ([a], [a]) Source
Inverse of interleave2
.
interleave2 ("abcd","ABCD") == "aAbBcCdD" deinterleave2 "aAbBcCdD" == ("abcd","ABCD")
Plotting
trace2_plot_3d :: [Trace R (R, R)] -> IO () Source
Three-dimensional plot of two-dimensional traces (time on x
axis), ie. plotPath
.