{-# LANGUAGE ForeignFunctionInterface, CPP #-} -- | Interface to loris.h module Sound.Loris.Foreign where import Foreign.C import Foreign.C.Types import Foreign.Marshal.Alloc import Foreign.Marshal.Array import Foreign.Ptr import Foreign.Storable #include -- ** Utility Marshalling Functions fI :: (Integral a, Num b) => a -> b fI = fromIntegral cIntConv :: (Integral a, Num b) => a -> b cIntConv = fromIntegral cFloatConv :: (Real a, Fractional b) => a -> b cFloatConv = realToFrac withCArray = withArray . map cFloatConv peekCD = fmap cFloatConv . peek allocPartialList f = do pl <- createPartialList f pl -- These are all opaque C pointers, so the Haskell versions need to be -- opaque as well. {#pointer *Breakpoint as BreakpointPtr newtype#} {#pointer *LinearEnvelope as LinearEnvelopePtr newtype#} {#pointer *PartialList as PartialListPtr newtype#} {#pointer *Partial as PartialPtr newtype#} -- ** Analyzers -- An Analyzer represents a configuration of parameters for -- performing Reassigned Bandwidth-Enhanced Additive Analysis -- of sampled waveforms. This analysis process yields a collection -- of Partials, each having a trio of synchronous, non-uniformly-sampled -- breakpoint envelopes representing the time-varying -- frequency, amplitude, and noisiness of a single bandwidth- -- enhanced sinusoid. -- -- For more information about Reassigned Bandwidth-Enhanced -- Analysis and the Reassigned Bandwidth-Enhanced Additive Sound -- Model, refer to the Loris website: www.cerlsoundgroup.org/Loris/. -- -- In the procedural interface, there is only one Analyzer. -- It must be configured by calling analyzer_configure before -- any of the other analyzer operations can be performed. -- | Analyze an array of bufferSize (mono) samples at the given sample rate -- (in Hz) and append the extracted Partials to the given -- PartialList. {#fun analyze as ^ { id `Ptr CDouble', `Int', `Double', id `PartialListPtr' } -> `()'#} -- | Configure the sole Analyzer instance with the specified -- frequency resolution (minimum instantaneous frequency -- difference between Partials). All other Analyzer parameters -- are computed from the specified frequency resolution. -- Construct the Analyzer instance if necessary. -- In the procedural interface, there is only one Analyzer. -- It must be configured by calling analyzer_configure before -- any of the other analyzer operations can be performed. {#fun analyzer_configure as ^ { `Double', -- ^ resolution `Double' -- ^ window width } -> `()'#} -- | Return the amplitude floor (lowest detected spectral amplitude), -- in (negative) dB, for the Loris Analyzer. {#fun unsafe analyzer_getAmpFloor as ^ { } -> `Double'#} -- | Return the crop time (maximum temporal displacement of a time- -- frequency data point from the time-domain center of the analysis -- window, beyond which data points are considered "unreliable") -- for the Loris Analyzer. {#fun unsafe analyzer_getCropTime as ^ { } -> `Double'#} -- | Return the maximum allowable frequency difference between -- consecutive Breakpoints in a Partial envelope for the Loris Analyzer. {#fun unsafe analyzer_getFreqDrift as ^ { } -> `Double'#} -- | Return the frequency floor (minimum instantaneous Partial -- frequency), in Hz, for the Loris Analyzer. {#fun unsafe analyzer_getFreqFloor as ^ { } -> `Double'#} -- | Return the frequency resolution (minimum instantaneous frequency -- difference between Partials) for the Loris Analyzer. {#fun unsafe analyzer_getFreqResolution as ^ { } -> `Double'#} -- | Return the hop time (which corresponds approximately to the -- average density of Partial envelope Breakpoint data) for this -- Analyzer. {#fun unsafe analyzer_getHopTime as ^ { } -> `Double'#} -- | Return the sidelobe attenutation level for the Kaiser analysis window in -- positive dB. Higher numbers (e.g. 90) give very good sidelobe -- rejection but cause the window to be longer in time. Smaller -- numbers raise the level of the sidelobes, increasing the likelihood -- of frequency-domain interference, but allow the window to be shorter -- in time. {#fun unsafe analyzer_getSidelobeLevel as ^ { } -> `Double'#} -- | Return the frequency-domain main lobe width (measured between -- zero-crossings) of the analysis window used by the Loris Analyzer. {#fun unsafe analyzer_getWindowWidth as ^ { } -> `Double'#} -- | Set the amplitude floor (lowest detected spectral amplitude), in -- (negative) dB, for the Loris Analyzer. {#fun unsafe analyzer_setAmpFloor as ^ { `Double' } -> `()'#} -- | Set the crop time (maximum temporal displacement of a time- -- frequency data point from the time-domain center of the analysis -- window, beyond which data points are considered "unreliable") -- for the Loris Analyzer. {#fun unsafe analyzer_setCropTime as ^ { `Double' } -> `()'#} -- | Set the maximum allowable frequency difference between -- consecutive Breakpoints in a Partial envelope for the Loris Analyzer. {#fun unsafe analyzer_setFreqDrift as ^ { `Double' } -> `()'#} -- | Set the amplitude floor (minimum instantaneous Partial -- frequency), in Hz, for the Loris Analyzer. {#fun unsafe analyzer_setFreqFloor as ^ { `Double' } -> `()'#} -- | Set the frequency resolution (minimum instantaneous frequency -- difference between Partials) for the Loris Analyzer. (Does not cause -- other parameters to be recomputed.) {#fun unsafe analyzer_setFreqResolution as ^ { `Double' } -> `()'#} -- | Set the hop time (which corresponds approximately to the average -- density of Partial envelope Breakpoint data) for the Loris Analyzer. {#fun unsafe analyzer_setHopTime as ^ { `Double' } -> `()'#} -- | Set the sidelobe attenutation level for the Kaiser analysis window in -- positive dB. Larger numbers (e.g. 90) give very good sidelobe -- rejection but cause the window to be longer in time. Smaller -- numbers raise the level of the sidelobes, increasing the likelihood -- of frequency-domain interference, but allow the window to be shorter -- in time. {#fun unsafe analyzer_setSidelobeLevel as ^ { `Double' } -> `()'#} -- | Set the frequency-domain main lobe width (measured between -- zero-crossings) of the analysis window used by the Loris Analyzer. {#fun unsafe analyzer_setWindowWidth as ^ { `Double' } -> `()'#} -- | Construct Partial bandwidth envelopes during analysis -- by associating residual energy in the spectrum (after -- peak extraction) with the selected spectral peaks that -- are used to construct Partials. -- -- regionWidth is the width (in Hz) of the bandwidth -- association regions used by this process, must be positive. {#fun unsafe analyzer_storeResidueBandwidth as ^ { `Double' } -> `()'#} -- | Construct Partial bandwidth envelopes during analysis -- by storing the mixed derivative of short-time phase, -- scaled and shifted so that a value of 0 corresponds -- to a pure sinusoid, and a value of 1 corresponds to a -- bandwidth-enhanced sinusoid with maximal energy spread -- (minimum sinusoidal convergence). -- -- tolerance is the amount of range over which the -- mixed derivative indicator should be allowed to drift away -- from a pure sinusoid before saturating. This range is mapped -- to bandwidth values on the range [0,1]. Must be positive and -- not greater than 1. {#fun unsafe analyzer_storeConvergenceBandwidth as ^ { `Double' } -> `()'#} -- | Disable bandwidth envelope construction. Bandwidth -- will be zero for all Breakpoints in all Partials. {#fun unsafe analyzer_storeNoBandwidth as ^ { } -> `()'#} -- | Return the width (in Hz) of the Bandwidth Association regions -- used by this Analyzer, only if the spectral residue method is -- used to compute bandwidth envelopes. Return zero if the mixed -- derivative method is used, or if no bandwidth is computed. {#fun unsafe analyzer_getBwRegionWidth as ^ { } -> `Double'#} -- | Return the mixed derivative convergence tolerance -- only if the convergence indicator is used to compute -- bandwidth envelopes. Return zero if the spectral residue -- method is used or if no bandwidth is computed. {#fun unsafe analyzer_getBwConvergenceTolerance as ^ { } -> `Double'#} -- ** LinearEnvelope interface -- -- A LinearEnvelope represents a linear segment breakpoint -- function with infinite extension at each end (that is, the -- values past either end of the breakpoint function have the -- values at the nearest end). -- | Construct and return a new LinearEnvelope having no -- breakpoints and an implicit value of 0. everywhere, -- until the first breakpoint is inserted. {#fun unsafe createLinearEnvelope as ^ { } -> `LinearEnvelopePtr' id #} -- | Construct and return a new LinearEnvelope that is an -- exact copy of the specified LinearEnvelopes, having -- an identical set of breakpoints. {#fun unsafe copyLinearEnvelope as ^ { id `LinearEnvelopePtr' } -> `LinearEnvelopePtr' id #} -- | Destroy this LinearEnvelope. {#fun unsafe destroyLinearEnvelope as ^ { id `LinearEnvelopePtr' } -> `()'#} -- | Insert a breakpoint representing the specified (time, value) -- pair into this LinearEnvelope. If there is already a -- breakpoint at the specified time, it will be replaced with -- the new breakpoint. {#fun unsafe linearEnvelope_insertBreakpoint as ^ { id `LinearEnvelopePtr', `Double', `Double' } -> `()'#} -- | Return the interpolated value of this LinearEnvelope at the -- specified time. {#fun unsafe linearEnvelope_valueAt as ^ { id `LinearEnvelopePtr', `Double' } -> `Double'#} -- ** PartialList object interface -- A PartialList represents a collection of Bandwidth-Enhanced -- Partials, each having a trio of synchronous, non-uniformly- -- sampled breakpoint envelopes representing the time-varying -- frequency, amplitude, and noisiness of a single bandwidth- -- enhanced sinusoid. -- -- For more information about Bandwidth-Enhanced Partials and the -- Reassigned Bandwidth-Enhanced Additive Sound Model, refer to -- the Loris website: www.cerlsoundgroup.org/Loris/. -- | Return a new empty PartialList. {#fun unsafe createPartialList as ^ { } -> `PartialListPtr' id #} -- | Destroy this PartialList. {#fun unsafe destroyPartialList as ^ { id `PartialListPtr' } -> `()' #} -- | Remove (and destroy) all the Partials from this PartialList, -- leaving it empty. {#fun unsafe partialList_clear as ^ { id `PartialListPtr' } -> `()' #} -- | Make this PartialList a copy of the source PartialList by making -- copies of all of the Partials in the source and adding them to -- this PartialList. -- Argument order is "this, source" {#fun unsafe partialList_copy as ^ { id `PartialListPtr', id `PartialListPtr' } -> `()' #} -- | Return the number of Partials in this PartialList. {#fun unsafe partialList_size as ^ { id `PartialListPtr' } -> `Integer' fromIntegral #} -- | Splice all the Partials in the source PartialList onto the end of -- this PartialList, leaving the source empty. -- Argument order is "this, source" {#fun unsafe partialList_splice as ^ { id `PartialListPtr', id `PartialListPtr' } -> `()' #} -- ** Partial object interface -- -- A Partial represents a single component in the -- reassigned bandwidth-enhanced additive model. A Partial consists of a -- chain of Breakpoints describing the time-varying frequency, amplitude, -- and bandwidth (or noisiness) envelopes of the component, and a 4-byte -- label. The Breakpoints are non-uniformly distributed in time. For more -- information about Reassigned Bandwidth-Enhanced Analysis and the -- Reassigned Bandwidth-Enhanced Additive Sound Model, refer to the Loris -- website: www.cerlsoundgroup.org/Loris/. -- | Return the start time (seconds) for the specified Partial. {#fun unsafe partial_startTime as ^ { id `PartialPtr' } -> `Double' #} -- | Return the end time (seconds) for the specified Partial. {#fun unsafe partial_endTime as ^ { id `PartialPtr' } -> `Double' #} -- | Return the duration (seconds) for the specified Partial. {#fun unsafe partial_duration as ^ { id `PartialPtr' } -> `Double' #} -- | Return the initial phase (radians) for the specified Partial. {#fun unsafe partial_initialPhase as ^ { id `PartialPtr' } -> `Double' #} -- | Return the integer label for the specified Partial. {#fun unsafe partial_label as ^ { id `PartialPtr' } -> `Int' #} -- | Return the number of Breakpoints in the specified Partial. {#fun unsafe partial_numBreakpoints as ^ { id `PartialPtr' } -> `Integer' fromIntegral #} -- | Return the frequency (Hz) of the specified Partial interpolated -- at a particular time. It is an error to apply this function to -- a Partial having no Breakpoints. {#fun unsafe partial_frequencyAt as ^ { id `PartialPtr', `Double' } -> `Double' #} -- | Return the bandwidth of the specified Partial interpolated -- at a particular time. It is an error to apply this function to -- a Partial having no Breakpoints. {#fun unsafe partial_bandwidthAt as ^ { id `PartialPtr', `Double' } -> `Double' #} -- | Return the phase (radians) of the specified Partial interpolated -- at a particular time. It is an error to apply this function to -- a Partial having no Breakpoints. {#fun unsafe partial_phaseAt as ^ { id `PartialPtr', `Double' } -> `Double' #} -- | Return the (absolute) amplitude of the specified Partial interpolated -- at a particular time. Partials are assumed to fade out -- over 1 millisecond at the ends (rather than instantaneously). -- It is an error to apply this function to a Partial having no Breakpoints. {#fun unsafe partial_amplitudeAt as ^ { id `PartialPtr', `Double' } -> `Double' #} -- | Assign a new integer label to the specified Partial. {#fun unsafe partial_setLabel as ^ { id `PartialPtr', `Int' } -> `()' #} -- ** Breakpoint object interface -- A Breakpoint represents a single breakpoint in the -- Partial parameter (frequency, amplitude, bandwidth) envelope. -- Instantaneous phase is also stored, but is only used at the onset of -- a partial, or when it makes a transition from zero to nonzero amplitude. -- -- Loris Partials represent reassigned bandwidth-enhanced model components. -- A Partial consists of a chain of Breakpoints describing the time-varying -- frequency, amplitude, and bandwidth (noisiness) of the component. -- For more information about Reassigned Bandwidth-Enhanced -- Analysis and the Reassigned Bandwidth-Enhanced Additive Sound -- Model, refer to the Loris website: -- www.cerlsoundgroup.org/Loris/. -- | Return the (absolute) amplitude of the specified Breakpoint. {#fun unsafe breakpoint_getAmplitude as ^ { id `BreakpointPtr' } -> `Double' #} -- | Return the bandwidth coefficient of the specified Breakpoint. {#fun unsafe breakpoint_getBandwidth as ^ { id `BreakpointPtr' } -> `Double' #} -- | Return the frequency (Hz) of the specified Breakpoint. {#fun unsafe breakpoint_getFrequency as ^ { id `BreakpointPtr' } -> `Double' #} -- | Return the phase (radians) of the specified Breakpoint. {#fun unsafe breakpoint_getPhase as ^ { id `BreakpointPtr' } -> `Double' #} -- | Assign a new (absolute) amplitude to the specified Breakpoint. {#fun unsafe breakpoint_setAmplitude as ^ { id `BreakpointPtr', `Double' } -> `()' #} -- | Assign a new bandwidth coefficient to the specified Breakpoint. {#fun unsafe breakpoint_setBandwidth as ^ { id `BreakpointPtr', `Double' } -> `()' #} -- | Assign a new frequency (Hz) to the specified Breakpoint. {#fun unsafe breakpoint_setFrequency as ^ { id `BreakpointPtr', `Double' } -> `()' #} -- | Assign a new phase (radians) to the specified Breakpoint. {#fun unsafe breakpoint_setPhase as ^ { id `BreakpointPtr', `Double' } -> `()' #} -- ** non-object-based procedures -- -- Operations in Loris that need not be accessed though object -- interfaces are represented as simple functions. -- | Label Partials in a PartialList with the integer nearest to -- the amplitude-weighted average ratio of their frequency envelope -- to a reference frequency envelope. The frequency spectrum is -- partitioned into non-overlapping channels whose time-varying -- center frequencies track the reference frequency envelope. -- The reference label indicates which channel's center frequency -- is exactly equal to the reference envelope frequency, and other -- channels' center frequencies are multiples of the reference -- envelope frequency divided by the reference label. Each Partial -- in the PartialList is labeled with the number of the channel -- that best fits its frequency envelope. The quality of the fit -- is evaluated at the breakpoints in the Partial envelope and -- weighted by the amplitude at each breakpoint, so that high- -- amplitude breakpoints contribute more to the channel decision. -- Partials are labeled, but otherwise unmodified. In particular, -- their frequencies are not modified in any way. {#fun unsafe channelize as ^ { id `PartialListPtr', id `LinearEnvelopePtr', `Int' } -> `()' #} -- | Collate unlabeled (zero-labeled) Partials into the smallest-possible -- number of Partials that does not combine any overlapping Partials. -- Collated Partials appear at the end of the sequence, after all -- labeled Partials. {#fun unsafe collate { id `PartialListPtr' } -> `()' #} -- | Return a newly-constructed LinearEnvelope using the legacy -- FrequencyReference class. The envelope will have approximately -- the specified number of samples. The specified number of samples -- must be greater than 1. Uses the FundamentalEstimator -- (FundamentalFromPartials) class to construct an estimator of -- fundamental frequency, configured to emulate the behavior of -- the FrequencyReference class in Loris 1.4-1.5.2. If numSamps -- is zero, construct the reference envelope from fundamental -- estimates taken every five milliseconds. -- -- For simple sounds, this frequency reference may be a -- good first approximation to a reference envelope for -- channelization (see channelize()). -- -- Clients are responsible for disposing of the newly-constructed -- LinearEnvelope. {#fun unsafe createFreqReference { id `PartialListPtr', `Double', `Double', fI `Integer' } -> `LinearEnvelopePtr' id #} -- | Return a newly-constructed LinearEnvelope that estimates -- the time-varying fundamental frequency of the sound -- represented by the Partials in a PartialList. This uses -- the FundamentalEstimator (FundamentalFromPartials) -- class to construct an estimator of fundamental frequency, -- and returns a LinearEnvelope that samples the estimator at the -- specified time interval (in seconds). Default values are used -- to configure the estimator. Only estimates in the specified -- frequency range will be considered valid, estimates outside this -- range will be ignored. -- -- Clients are responsible for disposing of the newly-constructed -- LinearEnvelope. {#fun unsafe createF0Estimate { id `PartialListPtr', `Double', `Double', `Double' } -> `LinearEnvelopePtr' id #} -- | Dilate Partials in a PartialList according to the given -- initial and target time points. Partial envelopes are -- stretched and compressed so that temporal features at -- the initial time points are aligned with the final time -- points. Time points are sorted, so Partial envelopes are -- are only stretched and compressed, but breakpoints are not -- reordered. Duplicate time points are allowed. There must be -- the same number of initial and target time points. {#fun unsafe dilate { id `PartialListPtr', withCArray* `[Double]', withCArray* `[Double]', `Int' } -> `()' #} -- | Distill labeled (channelized) Partials in a PartialList into a -- PartialList containing at most one Partial per label. Unlabeled -- (zero-labeled) Partials are left unmodified at the end of the -- distilled Partials. {#fun unsafe distill { id `PartialListPtr' } -> `()' #} -- | Apply a reference Partial to fix the frequencies of Breakpoints -- whose amplitude is below threshold_dB. 0 harmonifies full-amplitude -- Partials, to apply only to quiet Partials, specify a lower -- threshold like -90). The reference Partial is the first Partial -- in the PartialList labeled refLabel (usually 1). The LinearEnvelope -- is a time-varying weighting on the harmonifing process. When 1, -- harmonic frequencies are used, when 0, breakpoint frequencies are -- unmodified. {#fun unsafe harmonify { id `PartialListPtr', fI `Integer', id `LinearEnvelopePtr', `Double' } -> `()' #} -- | Morph labeled Partials in two PartialLists according to the -- given frequency, amplitude, and bandwidth (noisiness) morphing -- envelopes, and append the morphed Partials to the destination -- PartialList. Loris morphs Partials by interpolating frequency, -- amplitude, and bandwidth envelopes of corresponding Partials in -- the source PartialLists. For more information about the Loris -- morphing algorithm, see the Loris website: -- www.cerlsoundgroup.org/Loris/ {#fun morph { id `PartialListPtr', -- ^ src0 id `PartialListPtr', -- ^ src1 id `LinearEnvelopePtr', -- ^ ffreq id `LinearEnvelopePtr', -- ^ famp id `LinearEnvelopePtr', -- ^ fbw allocPartialList- `PartialListPtr' id } -> `()' #} -- | Morph labeled Partials in two PartialLists according to the -- given frequency, amplitude, and bandwidth (noisiness) morphing -- envelopes, and append the morphed Partials to the destination -- PartialList. Specify the labels of the Partials to be used as -- reference Partial for the two morph sources. The reference -- partial is used to compute frequencies for very low-amplitude -- Partials whose frequency estimates are not considered reliable. -- The reference Partial is considered to have good frequency -- estimates throughout. A reference label of 0 indicates that -- no reference Partial should be used for the corresponding -- morph source. -- -- Loris morphs Partials by interpolating frequency, -- amplitude, and bandwidth envelopes of corresponding Partials in -- the source PartialLists. For more information about the Loris -- morphing algorithm, see the Loris website: -- www.cerlsoundgroup.org/Loris/ {#fun morphWithReference { id `PartialListPtr', -- ^ src0 id `PartialListPtr', -- ^ src1 fI `Integer', -- ^ src0 ref label fI `Integer', -- ^ src1 ref label id `LinearEnvelopePtr', -- ^ ffreq id `LinearEnvelopePtr', -- ^ famp id `LinearEnvelopePtr', -- ^ fbw allocPartialList- `PartialListPtr' id } -> `()' #} -- | Set the shaping parameter for the amplitude morphing -- function. This shaping parameter controls the slope of -- the amplitude morphing function, for values greater than -- 1, this function gets nearly linear (like the old -- amplitude morphing function), for values much less than -- 1 (e.g. 1E-5) the slope is gently curved and sounds -- pretty "linear", for very small values (e.g. 1E-12) the -- curve is very steep and sounds un-natural because of the -- huge jump from zero amplitude to very small amplitude. -- -- Use LORIS_DEFAULT_AMPMORPHSHAPE to obtain the default -- amplitude morphing shape for Loris, (equal to 1E-5, -- which works well for many musical instrument morphs, -- unless Loris was compiled with the symbol -- LINEAR_AMP_MORPHS defined, in which case -- LORIS_DEFAULT_AMPMORPHSHAPE is equal to -- LORIS_LINEAR_AMPMORPHSHAPE). -- -- Use LORIS_LINEAR_AMPMORPHSHAPE to approximate the linear -- amplitude morphs performed by older versions of Loris. -- -- The amplitude shape must be positive. {#fun unsafe morpher_setAmplitudeShape as ^ { `Double' } -> `()' #} -- | Resample all Partials in a PartialList using the specified -- sampling interval, so that the Breakpoints in the Partial -- envelopes will all lie on a common temporal grid. -- The Breakpoint times in resampled Partials will comprise a -- contiguous sequence of integer multiples of the sampling interval, -- beginning with the multiple nearest to the Partial's start time and -- ending with the multiple nearest to the Partial's end time. Resampling -- is performed in-place. {#fun unsafe resample { id `PartialListPtr', `Double' } -> `()' #} -- | Scale the amplitudes of a set of Partials by applying -- a spectral suface constructed from another set. -- Stretch the spectral surface in time and frequency -- using the specified stretch factors. Set the stretch -- factors to one for no stretching. {#fun unsafe shapeSpectrum { id `PartialListPtr', -- ^ partials id `PartialListPtr', -- ^ surface `Double', -- ^ stretchFreq `Double' -- ^ stretchTime } -> `()' #} -- | Identify overlapping Partials having the same (nonzero) -- label. If any two partials with same label -- overlap in time, set the label of the weaker -- (having less total energy) partial to zero. {#fun unsafe sift { id `PartialListPtr' -- ^ partials } -> `()' #} -- | Synthesize Partials in a PartialList at the given sample -- rate, and store the (floating point) samples in a buffer of -- size bufferSize. The buffer is neither resized nor -- cleared before synthesis, so newly synthesized samples are -- added to any previously computed samples in the buffer, and -- samples beyond the end of the buffer are lost. Return the -- number of samples synthesized, that is, the index of the -- latest sample in the buffer that was modified. {#fun synthesize { id `PartialListPtr', -- ^ partials id `Ptr CDouble', -- ^ buffer fI `Integer', -- ^ bufferSize `Double' -- ^ srate } -> `Integer' fI #} -- ** utility functions -- -- Operations for transforming and manipulating collections -- of Partials. -- | Return the average amplitude over all Breakpoints in this Partial. -- Return zero if the Partial has no Breakpoints. {#fun unsafe avgAmplitude { id `PartialPtr' } -> `Double' #} -- | Return the average frequency over all Breakpoints in this Partial. -- Return zero if the Partial has no Breakpoints. {#fun unsafe avgFrequency { id `PartialPtr' } -> `Double' #} -- | A predicate function that operates on a partial type PartialPred = PartialPtr -> Ptr () -> IO CInt foreign import ccall "wrapper" mkPartialPred :: PartialPred -> IO (FunPtr PartialPred) -- | Append copies of Partials in the source PartialList satisfying the -- specified predicate to the destination PartialList. The source list -- is unmodified. The data parameter can be used to -- supply extra user-defined data to the function. Pass nullPtr if no -- additional data is needed. {#fun copyIf { id `PartialListPtr', -- ^ src id `PartialListPtr', -- ^ dst id `FunPtr PartialPred', id `Ptr ()' } -> `()' #} -- | Append copies of Partials in the source PartialList having the -- specified label to the destination PartialList. The source list -- is unmodified. {#fun unsafe copyLabeled { id `PartialListPtr', -- ^ src fI `Integer', -- ^ lbl id `PartialListPtr' -- ^ dst } -> `()' #} -- | Trim Partials by removing Breakpoints outside a specified time span. -- Insert a Breakpoint at the boundary when cropping occurs. Remove -- any Partials that are left empty after cropping (Partials having no -- Breakpoints between t1 and t2). {#fun unsafe crop { id `PartialListPtr', -- ^ src `Double', -- ^ t1 `Double' -- ^ t2 } -> `()' #} -- | Remove Partials in the source PartialList satisfying the -- specified predicate from the source list and append them to -- the destination PartialList. The data parameter can be used to -- supply extra user-defined data to the function. Pass nullPtr if no -- additional data is needed. {#fun extractIf { id `PartialListPtr', -- ^ src id `PartialListPtr', -- ^ dst id `FunPtr PartialPred', id `Ptr ()' } -> `()' #} -- | Remove Partials in the source PartialList having the specified -- label from the source list and append them to the destination -- PartialList. {#fun unsafe extractLabeled { id `PartialListPtr', -- ^ src fI `Integer', -- ^ lbl id `PartialListPtr' -- ^ dst } -> `()' #} -- | Recompute phases of all Breakpoints later than the specified -- time so that the synthesized phases of those later Breakpoints -- matches the stored phase, as long as the synthesized phase at -- the specified time matches the stored (not recomputed) phase. -- -- Phase fixing is only applied to non-null (nonzero-amplitude) -- Breakpoints, because null Breakpoints are interpreted as phase -- reset points in Loris. If a null is encountered, its phase is -- corrected from its non-Null successor, if it has one, otherwise -- it is unmodified. {#fun unsafe fixPhaseAfter { id `PartialListPtr', -- ^ partials `Double' -- ^ time } -> `()' #} -- | Recompute phases of all Breakpoints in a Partial -- so that the synthesized phases match the stored phases, -- and the synthesized phase at (nearest) the specified -- time matches the stored (not recomputed) phase. -- -- Backward phase-fixing stops if a null (zero-amplitude) -- Breakpoint is encountered, because nulls are interpreted as -- phase reset points in Loris. If a null is encountered, the -- remainder of the Partial (the front part) is fixed in the -- forward direction, beginning at the start of the Partial. -- Forward phase fixing is only applied to non-null -- (nonzero-amplitude) Breakpoints. If a null is encountered, -- its phase is corrected from its non-Null successor, if -- it has one, otherwise it is unmodified. {#fun unsafe fixPhaseAt { id `PartialListPtr', -- ^ partials `Double' -- ^ time } -> `()' #} -- | Recompute phases of all Breakpoints earlier than the specified -- time so that the synthesized phases of those earlier Breakpoints -- matches the stored phase, and the synthesized phase at the -- specified time matches the stored (not recomputed) phase. -- -- Backward phase-fixing stops if a null (zero-amplitude) Breakpoint -- is encountered, because nulls are interpreted as phase reset -- points in Loris. If a null is encountered, the remainder of the -- Partial (the front part) is fixed in the forward direction, -- beginning at the start of the Partial. {#fun unsafe fixPhaseBefore { id `PartialListPtr', -- ^ partials `Double' -- ^ time } -> `()' #} -- | Fix the phase travel between two times by adjusting the -- frequency and phase of Breakpoints between those two times. -- -- This algorithm assumes that there is nothing interesting -- about the phases of the intervening Breakpoints, and modifies -- their frequencies as little as possible to achieve the correct -- amount of phase travel such that the frequencies and phases at -- the specified times match the stored values. The phases of all -- the Breakpoints between the specified times are recomputed. {#fun unsafe fixPhaseBetween { id `PartialListPtr', -- ^ partials `Double', -- ^ tbeg `Double' -- ^ tend } -> `()' #} -- | Recompute phases of all Breakpoints later than the specified -- time so that the synthesized phases of those later Breakpoints -- matches the stored phase, as long as the synthesized phase at -- the specified time matches the stored (not recomputed) phase. -- Breakpoints later than tend are unmodified. -- -- Phase fixing is only applied to non-null (nonzero-amplitude) -- Breakpoints, because null Breakpoints are interpreted as phase -- reset points in Loris. If a null is encountered, its phase is -- corrected from its non-Null successor, if it has one, otherwise -- it is unmodified. {#fun unsafe fixPhaseForward { id `PartialListPtr', -- ^ partials `Double', -- ^ tbeg `Double' -- ^ tend } -> `()' #} -- | Return the maximum amplitude achieved by a Partial. {#fun unsafe peakAmplitude { id `PartialPtr' -- ^ partial } -> `Double' #} -- | Remove from a PartialList all Partials satisfying the -- specified predicate. The data parameter can be used to -- supply extra user-defined data to the function. Pass nullPtr if no -- additional data is needed. {#fun removeIf { id `PartialListPtr', -- ^ src id `FunPtr PartialPred', id `Ptr ()' } -> `()' #} -- | Remove from a PartialList all Partials having the specified label. {#fun unsafe removeLabeled { id `PartialListPtr', -- ^ partials fI `Integer' -- ^ Label } -> `()' #} -- | Scale the amplitude of the Partials in a PartialList according -- to an envelope representing a time-varying amplitude scale value. {#fun unsafe scaleAmplitude { id `PartialListPtr', -- ^ partials id `LinearEnvelopePtr' -- ^ ampEnv } -> `()' #} -- | Scale the bandwidth of the Partials in a PartialList according -- to an envelope representing a time-varying bandwidth scale value. {#fun unsafe scaleBandwidth { id `PartialListPtr', -- ^ partials id `LinearEnvelopePtr' -- ^ bwEnv } -> `()' #} -- | Scale the frequency of the Partials in a PartialList according -- to an envelope representing a time-varying frequency scale value. {#fun unsafe scaleFrequency { id `PartialListPtr', -- ^ partials id `LinearEnvelopePtr' -- ^ freqEnv } -> `()' #} -- | Scale the relative noise content of the Partials in a PartialList -- according to an envelope representing a (time-varying) noise energy -- scale value. {#fun unsafe scaleNoiseRatio { id `PartialListPtr', -- ^ partials id `LinearEnvelopePtr' -- ^ noiseEnv } -> `()' #} -- | Set the bandwidth of the Partials in a PartialList according -- to an envelope representing a time-varying bandwidth value. {#fun unsafe setBandwidth { id `PartialListPtr', -- ^ partials id `LinearEnvelopePtr' -- ^ bwEnv } -> `()' #} -- | Shift the pitch of all Partials in a PartialList according to -- the given pitch envelope. The pitch envelope is assumed to have -- units of cents (1/100 of a halfstep). {#fun unsafe shiftPitch { id `PartialListPtr', -- ^ partials id `LinearEnvelopePtr' -- ^ pitchEnv } -> `()' #} -- | Shift the time of all the Breakpoints in a Partial by a -- constant amount. {#fun unsafe shiftTime { id `PartialListPtr', -- ^ partials `Double' -- ^ offset } -> `()' #} -- | Sort the Partials in a PartialList in order of increasing label. -- The sort is stable; Partials having the same label are not -- reordered. {#fun unsafe sortByLabel { id `PartialListPtr' -- ^ partials } -> `()' #} -- | Return the minimum start time and maximum end time -- in seconds of all Partials in this PartialList. {#fun unsafe timeSpan { id `PartialListPtr', -- ^ src alloca- `Double' peekCD*, alloca- `Double' peekCD* } -> `()' #} -- | Return the average frequency over all Breakpoints in this Partial, -- weighted by the Breakpoint amplitudes. Return zero if the Partial -- has no Breakpoints. {#fun unsafe weightedAvgFrequency { id `PartialPtr' -- ^ Partial } -> `Double' #} -- ** Audio file import/export -- | Export mono audio samples stored in an array of size bufferSize to -- an AIFF file having the specified sample rate at the given file path -- (or name). The floating point samples in the buffer are clamped to the -- range (-1.,1.) and converted to integers having bitsPerSamp bits. {#fun unsafe exportAiff { `String', id `Ptr CDouble', fI `Integer', `Double', `Int' } -> `()' #} -- | Export Partials in a PartialList to a SDIF file at the specified -- file path (or name). SDIF data is described by RBEM and RBEL -- matrices. -- For more information about SDIF, see the SDIF web site at: -- www.ircam.fr/equipes/analyse-synthese/sdif/ {#fun unsafe exportSdif { `String', id `PartialListPtr' } -> `()' #} -- | Export Partials in a PartialList to a Spc file at the specified file -- path (or name). The fractional MIDI pitch must be specified. The -- enhanced parameter defaults to true (for bandwidth-enhanced spc files), -- but an be specified false for pure-sines spc files. The endApproachTime -- parameter is in seconds. A nonzero endApproachTime indicates that the plist does -- not include a release, but rather ends in a static spectrum corresponding -- to the final breakpoint values of the partials. The endApproachTime -- specifies how long before the end of the sound the amplitude, frequency, -- and bandwidth values are to be modified to make a gradual transition to -- the static spectrum. {#fun unsafe exportSpc { `String', id `PartialListPtr', `Double', `Int', `Double' } -> `()' #} -- | Import audio samples stored in an AIFF file at the given file -- path (or name). The samples are converted to floating point -- values on the range (-1.,1.) and stored in an array of doubles. -- The value returned is the number of samples in buffer, and it is at -- most bufferSize. If samplerate is not a NULL pointer, -- then, on return, it points to the value of the sample rate (in -- Hz) of the AIFF samples. The AIFF file must contain only a single -- channel of audio data. The prior contents of buffer, if any, are -- overwritten. {#fun unsafe importAiff { `String', id `Ptr CDouble', `Int', alloca- `Double' peekCD* } -> `Int' #} -- | Import Partials from an SDIF file at the given file path (or -- name), and append them to a PartialList. {#fun unsafe importSdif { `String', allocPartialList- `PartialListPtr' id } -> `()' #} -- | Import Partials from an Spc file at the given file path (or -- name), and return them in a PartialList. {#fun unsafe importSpc { `String', allocPartialList- `PartialListPtr' id } -> `()' #} -- | Callback function type for "forEachBreakpoint". type BreakpointFunction = BreakpointPtr -> CDouble -> Ptr () -> IO CInt foreign import ccall "wrapper" mkBreakpointFunction :: BreakpointFunction -> IO (FunPtr BreakpointFunction) -- | Apply a function to each Breakpoint in a Partial. The function -- is called once for each Breakpoint in the source Partial. The -- function may modify the Breakpoint (but should not otherwise attempt -- to modify the Partial). The data parameter can be used to supply extra -- user-defined data to the function. Pass 0 if no additional data is needed. -- The function should return 0 if successful. If the function returns -- a non-zero value, then forEachBreakpoint immediately returns that value -- without applying the function to any other Breakpoints in the Partial. -- forEachBreakpoint returns zero if all calls to func return zero. {#fun forEachBreakpoint { id `PartialPtr', id `FunPtr BreakpointFunction', id `Ptr ()' } -> `Int' #} -- | Callback function type for "forEachBreakpoint". type PartialFunction = PartialPtr -> Ptr () -> IO CInt foreign import ccall "wrapper" mkPartialFunction :: PartialFunction -> IO (FunPtr PartialFunction) -- | Apply a function to each Partial in a PartialList. The function -- is called once for each Partial in the source PartialList. The -- function may modify the Partial (but should not attempt to modify -- the PartialList). The data parameter can be used to supply extra -- user-defined data to the function. Pass 0 if no additional data -- is needed. The function should return 0 if successful. If the -- function returns a non-zero value, then forEachPartial immediately -- returns that value without applying the function to any other -- Partials in the PartialList. forEachPartial returns zero if all -- calls to func return zero. {#fun forEachPartial { id `PartialListPtr', id `FunPtr PartialFunction', id `Ptr ()' } -> `Int' #} -- ** Notifiers and exception handlers -- | A callback function that takes a CString. type StringCallback = CString -> IO () foreign import ccall "wrapper" mkStringCallback :: StringCallback -> IO (FunPtr StringCallback) -- | Specify a function to call when reporting exceptions. The -- function takes a const char * argument, and returns void. {#fun setExceptionHandler { id `FunPtr StringCallback' } -> `()' #} -- | Specify a notification function. The function takes a -- const char * argument, and returns void. {#fun setNotifier { id `FunPtr StringCallback' } -> `()' #}