hommage-0.0.5: Haskell Offline Music Manipulation And Generation EDSLSource codeContentsIndex
Sound.Hommage.Envelope
Contents
Env
EnvLength
ADSR
Interpolate
Description
This module contains some functions and datatypes for envelopes. An envelope in generall is a kind of controll signal that modulates (for example) the volume of a sound in a non-periodic way (getting loud at the beginning and fading out at the end...). It is also used to controll the duration of a sound, since (here) envelopes always produce finite signals.
Synopsis
type Env = Int -> [Double]
runEnv :: [(Env, EnvLength)] -> Env
(<?>) :: IsEnv a => a -> EnvLength -> (Env, EnvLength)
class IsEnv a where
toEnv :: a -> Env
calculateEnvLengths :: Int -> [EnvLength] -> [Int]
data EnvLength
= Abs Int
| Abs_ Int
| Flex Double
| Rel (Ratio Int)
| Rel_ (Ratio Int)
type ADSR = (Int, Int, Double, Int)
data EnvShape
= Linear
| CosLike
data EnvMode
= HoldS
| FitS
| FitADR
playADSR :: EnvMode -> EnvShape -> ADSR -> Int -> [Double]
data Interpolate = Interpolate EnvShape (Double, Double)
data Constant = Constant Double
interpolate :: Fractional a => (a, a) -> Int -> [a]
interpolate_cos :: Floating a => (a, a) -> Int -> [a]
Documentation
An envelope is represented by a function of type Env. Such functions (or instances of class IsEnv) can be combined into a sequence where every Env is given a EnvLength (using the binary operator <?>. The whole sequence can be turnde into an Env (and be played then) with runEnv.
Env
type Env = Int -> [Double]Source
runEnv :: [(Env, EnvLength)] -> EnvSource
(<?>) :: IsEnv a => a -> EnvLength -> (Env, EnvLength)Source
class IsEnv a whereSource
Methods
toEnv :: a -> EnvSource
show/hide Instances
EnvLength
calculateEnvLengths :: Int -> [EnvLength] -> [Int]Source
Takes an absolute total length and a list of EnvLengths. Each EnvLength is mapped to its length with respect to the total length and a resuming length that is the result of total length - (all fixed lengths + all relative lengths) . This resuming lengths is distributed to the flexible lengths.
data EnvLength Source
EnvLength represents the length of a segment of an Envelope.
Constructors
Abs IntA fixed length.
Abs_ IntA fixed length that is not subtracted from the total time.
Flex DoubleA flexible length. Resuming length is distributed to all flexible lengths proportionally to its value.
Rel (Ratio Int)A length relative to the total length.
Rel_ (Ratio Int)A relative length that is not subtracted from the total time.
ADSR
type ADSR = (Int, Int, Double, Int)Source

The four components of ADSR are:

  • Attack (time to reach value 1.0, starting from 0.0)
  • Decay (time to reach sustain level)
  • Sustain (level to hold until note is released, should be a value between 0.0 and 1.0)
  • Release (time to reach value 0.0 after note is released)

time is measured in sample points, 44100 is one second.

data EnvShape Source
A linear or a cosinus-like shape
Constructors
Linear
CosLike
show/hide Instances
data EnvMode Source
Constructors
HoldSSustain value is kept until duration is over, Release part is appended.
FitSEnvelope has given duration by fitting only duration of constant Sustain level.
FitADRAttack, Decay and Released are together stretched to given duration.
show/hide Instances
playADSR :: EnvMode -> EnvShape -> ADSR -> Int -> [Double]Source
Playing an ADSR

Here is the code of playADSR to show the use of Env, <?> and EnvLength:

 playADSR :: EnvMode -> EnvShape -> ADSR -> Int -> [Double]
 playADSR mode shape (a,d,s,r) = case mode of
  FitADR -> runEnv
            [ Interpolate shape (0.0,1.0) <?> Flex (fromIntegral a)
            , Interpolate shape (1.0, s) <?> Flex (fromIntegral d)
            , Interpolate shape (s, 0.0) <?> Flex (fromIntegral r)
            ]
  FitS   -> runEnv
            [ Interpolate shape (0.0,1.0) <?> Abs a
            , Interpolate shape (1.0, s) <?> Abs d
            , Constant s <?> Flex 1.0
            , Interpolate shape (s, 0.0) <?> Abs r
            ]
  HoldS  -> runEnv
            [ Interpolate shape (0.0,1.0) <?> Abs a
            , Interpolate shape (1.0, s) <?> Abs d
            , Constant s <?> Flex 1.0
            , Interpolate shape (s, 0.0) <?> Abs_ r
            ]
Interpolate
data Interpolate Source
Constructors
Interpolate EnvShape (Double, Double)
show/hide Instances
data Constant Source
Constructors
Constant Double
show/hide Instances
interpolate :: Fractional a => (a, a) -> Int -> [a]Source
produces a line with given length that starts with fst value and ends with snd value
interpolate_cos :: Floating a => (a, a) -> Int -> [a]Source
produces a curve with given length that starts with fst value and ends with snd value. this curve has the shape of a half cosinus curve (values for 0 to PI).
Produced by Haddock version 2.4.2