haskore-0.1.0.3: The Haskore Computer Music SystemSource codeContentsIndex
Haskore.Interface.CSound.Generator
Synopsis
data T
= Routine Number [Parameter]
| SoundFile SFName SkipTime ChanNum
type SFName = String
type SkipTime = Time
type ChanNum = Float
type Number = Int
type Parameter = Float
soundFile :: SFName -> SkipTime -> ChanNum -> T
tableValues :: [Parameter] -> T
polynomial :: Interval -> Coefficients -> T
type Interval = (Float, Float)
type Coefficients = [Float]
exponential1 :: StartPt -> [(SegLength, EndPt)] -> T
type StartPt = Float
type SegLength = Float
type EndPt = Float
exponential2 :: [Point] -> T
type Point = (Float, Float)
cubic :: StartPt -> [(SegLength, EndPt)] -> T
lineSeg1 :: StartPt -> [(SegLength, EndPt)] -> T
lineSeg2 :: [Point] -> T
cubicSpline :: StartPt -> [(SegLength, EndPt)] -> T
compSine1 :: [PStrength] -> T
type PStrength = Float
compSine2 :: [(PNum, PStrength, PhaseOffset)] -> T
type PNum = Float
type PhaseOffset = Float
compSine3 :: [(PNum, PStrength, PhaseOffset, DCOffset)] -> T
type DCOffset = Float
cosineHarms :: NHarms -> LowestHarm -> Mult -> T
type NHarms = Int
type LowestHarm = Int
type Mult = Float
randomTable :: RandDist -> T
data RandDist
= Uniform
| Linear
| Triangular
| Expon
| BiExpon
| Gaussian
| Cauchy
| PosCauchy
toStatementWords :: T -> [String]
Documentation
data T Source
Constructors
Routine Number [Parameter]
SoundFile SFName SkipTime ChanNum
show/hide Instances
type SFName = StringSource
type SkipTime = TimeSource
type ChanNum = FloatSource
type Number = IntSource
type Parameter = FloatSource
soundFile :: SFName -> SkipTime -> ChanNum -> TSource
tableValues :: [Parameter] -> TSource
polynomial :: Interval -> Coefficients -> TSource
type Interval = (Float, Float)Source
type Coefficients = [Float]Source
exponential1 :: StartPt -> [(SegLength, EndPt)] -> TSource
type StartPt = FloatSource
type SegLength = FloatSource
type EndPt = FloatSource
exponential2 :: [Point] -> TSource
type Point = (Float, Float)Source
coordinates. The folowing pair will determine the next local minimum/maximum, followed by the second point of inflexion, etc. begin{haskelllisting}
cubic :: StartPt -> [(SegLength, EndPt)] -> TSource
lineSeg1 :: StartPt -> [(SegLength, EndPt)] -> TSource
lineSeg2 :: [Point] -> TSource
cubicSpline :: StartPt -> [(SegLength, EndPt)] -> TSource
compSine1 :: [PStrength] -> TSource
type PStrength = FloatSource
compSine2 :: [(PNum, PStrength, PhaseOffset)] -> TSource
type PNum = FloatSource
type PhaseOffset = FloatSource
compSine3 :: [(PNum, PStrength, PhaseOffset, DCOffset)] -> TSource
type DCOffset = FloatSource
where $r$ is the multiplier). begin{haskelllisting}
cosineHarms :: NHarms -> LowestHarm -> Mult -> TSource
type NHarms = IntSource
type LowestHarm = IntSource
type Mult = FloatSource
randomTable :: RandDist -> TSource
data RandDist Source
Constructors
Uniform
Linear
Triangular
Expon
BiExpon
Gaussian
Cauchy
PosCauchy
show/hide Instances
toStatementWords :: T -> [String]Source
Produced by Haddock version 2.6.1