ParentContentsIndex
Sound.Hommage.Play
Contents
Play
Interpretation of Notation for Play
Parallel played and hierarchical defined tracks
Environment
Duration
Synopsis
newtype Play a = PLAY {
unPlay :: (Duration -> Environment -> a)
}
getDur :: Play Dur
resetDur :: Play a -> Play a
randomPlay :: (Random a) => (a, a) -> Play a
mix :: [Play Signal] -> Play Signal
mix' :: (Num a) => [Play [a]] -> Play [a]
notationMono :: Notation (Play Signal) -> Play [Mono]
notationStereo :: Notation (Play Signal) -> Play [Stereo]
notation :: (Mixable a) => Notation (Play a) -> Play a
class Mixable a where
mixdown :: Seq a -> a
data Song a = SONG {
unSong :: (Duration -> Environment -> (a, Environment))
}
runSong :: Double -> Song (Play a) -> a
newtype Track a = TRACK {
unTrack :: (Environment -> a)
}
playTrack :: Track a -> Play a
track :: (Trackable a) => Play a -> Song (Track a)
class (Typeable a) => Trackable a where
toNext :: a -> a
newtype Environment = Environment (Int, [(Int, [Dynamic])])
emptyEnvironment :: Environment
nextEnvironment :: Environment -> Environment
insertEnvironment :: [Dynamic] -> Environment -> (Environment -> Dynamic, Environment)
lookupEnvironment :: Int -> Environment -> Dynamic
data Duration = DURATION {
relativeDuration :: Dur
absoluteDuration :: Dur
}
resetDuration :: Duration -> Duration
initDuration :: Dur -> Duration
Play
newtype Play a
Constructors
PLAY
unPlay :: (Duration -> Environment -> a)
Instances
Monad Play
Functor Play
Stretchable (Play a)
Sound (Play Signal)
Sound (Play [Mono])
Sound (Play [Stereo])
(Sound a) => Effect (Play Signal -> a)
(Sound a) => Effect (Play [Mono] -> a)
(Sound a) => Effect (Play [Stereo] -> a)
Effect (Play (Signal -> Signal))
getDur :: Play Dur
resetDur :: Play a -> Play a
randomPlay :: (Random a) => (a, a) -> Play a
mix :: [Play Signal] -> Play Signal
mix' :: (Num a) => [Play [a]] -> Play [a]
Interpretation of Notation for Play
notationMono :: Notation (Play Signal) -> Play [Mono]
notationStereo :: Notation (Play Signal) -> Play [Stereo]
notation :: (Mixable a) => Notation (Play a) -> Play a
class Mixable a where
Methods
mixdown :: Seq a -> a
Instances
(Num a) => Mixable [a]
Parallel played and hierarchical defined tracks
data Song a
Constructors
SONG
unSong :: (Duration -> Environment -> (a, Environment))
Instances
Functor Song
Monad Song
runSong :: Double -> Song (Play a) -> a
newtype Track a
Constructors
TRACK
unTrack :: (Environment -> a)
Instances
Functor Track
Sound (Track Signal)
Sound (Track [Mono])
Sound (Track [Stereo])
playTrack :: Track a -> Play a
track :: (Trackable a) => Play a -> Song (Track a)
class (Typeable a) => Trackable a where
Methods
toNext :: a -> a
Instances
Trackable Signal
(Typeable a) => Trackable [a]
Environment
newtype Environment
Constructors
Environment (Int, [(Int, [Dynamic])])
emptyEnvironment :: Environment
nextEnvironment :: Environment -> Environment
insertEnvironment :: [Dynamic] -> Environment -> (Environment -> Dynamic, Environment)
lookupEnvironment :: Int -> Environment -> Dynamic
Duration
data Duration
Constructors
DURATION
relativeDuration :: Dur
absoluteDuration :: Dur
Instances
IsDur Duration
resetDuration :: Duration -> Duration
initDuration :: Dur -> Duration
Produced by Haddock version HADDOCK_VERSION