Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Evt a = Evt {}
- type Bam a = a -> SE ()
- type Tick = Evt Unit
- boolToEvt :: BoolSig -> Evt Unit
- evtToBool :: Evt a -> BoolSig
- evtToTrig :: Evt a -> Sig
- sigToEvt :: Sig -> Evt Unit
- evtToSig :: D -> Evt D -> Sig
- stepper :: Tuple a => a -> Evt a -> SE a
- filterE :: (a -> BoolSig) -> Evt a -> Evt a
- filterSE :: (a -> SE BoolSig) -> Evt a -> Evt a
- accumSE :: Tuple s => s -> (a -> s -> SE (b, s)) -> Evt a -> Evt b
- accumE :: Tuple s => s -> (a -> s -> (b, s)) -> Evt a -> Evt b
- filterAccumE :: Tuple s => s -> (a -> s -> (BoolSig, b, s)) -> Evt a -> Evt b
- filterAccumSE :: Tuple s => s -> (a -> s -> SE (BoolSig, b, s)) -> Evt a -> Evt b
- type family Snap a
- snapshot :: (Tuple a, Tuple (Snap a)) => (Snap a -> b -> c) -> a -> Evt b -> Evt c
- readSnap :: (Tuple (Snap a), Tuple a) => a -> Snap a
- snaps :: Sig -> Evt D
- snaps2 :: Sig2 -> Evt (D, D)
- sync :: (Default a, Tuple a) => Sig -> Evt a -> Evt a
- syncBpm :: (Default a, Tuple a) => Sig -> Evt a -> Evt a
- metro :: Sig -> Evt Unit
- gaussTrig :: Sig -> Sig -> Tick
- dust :: Sig -> Tick
- metroSig :: Sig -> Sig
- dustSig :: Sig -> SE Sig
- dustSig2 :: Sig -> SE Sig
- impulseE :: D -> Evt Unit
- changedE :: [Sig] -> Evt Unit
- triggerE :: Sig -> Sig -> Sig -> Evt Unit
- loadbang :: Evt Unit
- impulse :: D -> Sig
- metroE :: Sig -> Evt Unit
- delEvt :: Arg a => D -> Evt a -> Evt a
- devt :: D -> Evt a -> Evt D
- eventList :: [(Sig, Sig, a)] -> Evt (Sco a)
- cycleE :: (Tuple a, Arg a) => [a] -> Evt b -> Evt a
- iterateE :: Tuple a => a -> (a -> a) -> Evt b -> Evt a
- repeatE :: Tuple a => a -> Evt b -> Evt a
- appendE :: Tuple a => a -> (a -> a -> a) -> Evt a -> Evt a
- mappendE :: (Monoid a, Tuple a) => Evt a -> Evt a
- partitionE :: (a -> BoolSig) -> Evt a -> (Evt a, Evt a)
- takeE :: Int -> Evt a -> Evt a
- dropE :: Int -> Evt a -> Evt a
- takeWhileE :: (a -> BoolSig) -> Evt a -> Evt a
- dropWhileE :: (a -> BoolSig) -> Evt a -> Evt a
- splitToggle :: Evt D -> (Evt D, Evt D)
- toTog :: Tick -> Evt D
- toTog1 :: Tick -> Evt D
- type Rnds a = [(Sig, a)]
- oneOf :: (Tuple a, Arg a) => [a] -> Evt b -> Evt a
- freqOf :: (Tuple a, Arg a) => Rnds a -> Evt b -> Evt a
- freqAccum :: (Arg b, Arg s) => s -> (a -> s -> Rnds (b, s)) -> Evt a -> Evt b
- randDs :: Evt b -> Evt D
- randList :: Int -> Evt b -> Evt [D]
- randInts :: (D, D) -> Evt b -> Evt Sig
- randSkip :: Sig -> Evt a -> Evt a
- randSkipBy :: (a -> Sig) -> Evt a -> Evt a
- range :: (D, D) -> Evt b -> Evt Sig
- listAt :: (Tuple a, Arg a) => [a] -> Evt Sig -> Evt a
- every :: (Tuple a, Arg a) => Int -> [Int] -> Evt a -> Evt a
- masked :: Tuple a => [Sig] -> Evt a -> Evt a
Documentation
A stream of events. We can convert a stream of events to
the procedure with the function runEvt
. It waits for events
and invokes the given procedure when the event happens.
Core functions
evtToBool :: Evt a -> BoolSig Source #
Converts an event stream to boolean signal. It's True when something happens and False otherwise.
evtToTrig :: Evt a -> Sig Source #
Creates a trigger signal out of event stream. It equals to 1 when something happens and 0 otherwise.
evtToSig :: D -> Evt D -> Sig Source #
Converts event stream to signal. The first argument is initial value. It holds the value while nothing happens. If the event happens it overwrites the current value of the output signal.
accumSE :: Tuple s => s -> (a -> s -> SE (b, s)) -> Evt a -> Evt b #
Accumulator for events with side effects.
filterAccumE :: Tuple s => s -> (a -> s -> (BoolSig, b, s)) -> Evt a -> Evt b #
Accumulator with filtering. It can skip the events from the event stream. If the third element of the triple equals to 1 then we should include the event in the resulting stream. If the element equals to 0 we skip the event.
filterAccumSE :: Tuple s => s -> (a -> s -> SE (BoolSig, b, s)) -> Evt a -> Evt b #
Accumulator for events with side effects and filtering. Event triggers only if the first element in the tripplet is true.
A snapshot of the signal. It converts a type of the signal to the type of the value in the given moment. Instances:
type instance Snap D = D type instance Snap Str = Str type instance Snap Tab = Tab type instance Snap Sig = D type instance Snap (a, b) = (Snap a, Snap b) type instance Snap (a, b, c) = (Snap a, Snap b, Snap c) type instance Snap (a, b, c, d) = (Snap a, Snap b, Snap c, Snap d) type instance Snap (a, b, c, d, e) = (Snap a, Snap b, Snap c, Snap d, Snap e) type instance Snap (a, b, c, d, e, f) = (Snap a, Snap b, Snap c, Snap d, Snap e, Snap f)
Instances
type Snap D | |
Defined in Csound.Typed.Types.Evt | |
type Snap Sig | |
Defined in Csound.Typed.Types.Evt | |
type Snap Str | |
Defined in Csound.Typed.Types.Evt | |
type Snap Tab | |
Defined in Csound.Typed.Types.Evt | |
type Snap (a, b) | |
Defined in Csound.Typed.Types.Evt | |
type Snap (a, b, c) | |
Defined in Csound.Typed.Types.Evt | |
type Snap (a, b, c, d) | |
type Snap (a, b, c, d, e) | |
type Snap (a, b, c, d, e, f) | |
snapshot :: (Tuple a, Tuple (Snap a)) => (Snap a -> b -> c) -> a -> Evt b -> Evt c #
Get values of some signal at the given events.
Constructs an event stream that contains values from the given signal. Events happens only when the signal changes.
snaps2 :: Sig2 -> Evt (D, D) Source #
Constructs an event stream that contains pairs from the given pair of signals. Events happens when any signal changes.
sync :: (Default a, Tuple a) => Sig -> Evt a -> Evt a #
Executes actions synchronized with global tempo (in Hz).
runEvtSync tempoCps evt proc
syncBpm :: (Default a, Tuple a) => Sig -> Evt a -> Evt a Source #
the sync function but time is measured in beats per minute.
Opcodes
gaussTrig :: Sig -> Sig -> Tick Source #
Creates a stream of ticks that happen around the given frequency with given deviation.
gaussTrig freq deviation
Creates a stream of random events. The argument is a number of events per second.
dust eventsPerSecond
dustSig :: Sig -> SE Sig Source #
Creates a signal that contains a random ones that happen with given frequency.
dustSig2 :: Sig -> SE Sig Source #
Creates a signal that contains a random ones or negative ones that happen with given frequency.
triggerE :: Sig -> Sig -> Sig -> Evt Unit Source #
Behaves like trigger
, but returns an event stream.
metroE :: Sig -> Evt Unit Source #
Deprecated: Use metro instead
Behaves like metro
, but returns an event stream.
Higher-level event functions
devt :: D -> Evt a -> Evt D Source #
Constant event stream. It produces the same value (the first argument) all the time.
cycleE :: (Tuple a, Arg a) => [a] -> Evt b -> Evt a Source #
Constructs an event stream that contains an infinite repetition values from the given list. When an event happens this function takes the next value from the list, if there is no values left it starts from the beggining of the list.
iterateE :: Tuple a => a -> (a -> a) -> Evt b -> Evt a Source #
When something happens on the given event stream resulting event stream contains an application of some unary function to the given initial value. So the event stream contains the values:
[s0, f s0, f (f s0), f (f (f s0)), ...]
repeatE :: Tuple a => a -> Evt b -> Evt a Source #
Substitutes all values in the input stream with the given constant value.
appendE :: Tuple a => a -> (a -> a -> a) -> Evt a -> Evt a Source #
Accumulates a values from the given event stream with binary function. It's a variant of the fold for event streams.
appendE z f evt
When value a
happens with evt
, the resulting event stream contains
a value (z f
a) and in the next time z
equals to this value.
partitionE :: (a -> BoolSig) -> Evt a -> (Evt a, Evt a) Source #
Splits event stream on two streams with predicate.
takeE :: Int -> Evt a -> Evt a Source #
Takes the ns events from the event stream and ignores the rest of the stream.
dropE :: Int -> Evt a -> Evt a Source #
Drops the ns events from the event stream and leaves the rest of the stream.
splitToggle :: Evt D -> (Evt D, Evt D) Source #
Splits a toggle event stream on on-events and off-events.
toTog1 :: Tick -> Evt D Source #
Converts clicks to alternating 1 and 0 (toggle event stream with first value set to 1)
oneOf :: (Tuple a, Arg a) => [a] -> Evt b -> Evt a Source #
Constructs an event stream that contains values from the given list which are taken in the random order.
freqOf :: (Tuple a, Arg a) => Rnds a -> Evt b -> Evt a Source #
Constructs an event stream that contains values from the given list which are taken in the random order. In the list we specify not only values but the frequencies of occurrence. Sum of the frequencies should be equal to one.
freqAccum :: (Arg b, Arg s) => s -> (a -> s -> Rnds (b, s)) -> Evt a -> Evt b Source #
This function combines the functions accumE
and
freqOf
. We transform the values of the event stream
with stateful function that produce not just values but the list of values
with frequencies of occurrence. We apply this function to the current state
and the value and then at random pick one of the values.
randList :: Int -> Evt b -> Evt [D] Source #
An event stram of lists of random values in the interval (0, 1)
.
The first argument is the length of the each list.
randInts :: (D, D) -> Evt b -> Evt Sig Source #
An event stream of the integers taken from the given diapason.
randSkip :: Sig -> Evt a -> Evt a Source #
Skips elements at random.
randSkip prob
where prob
is probability of includinng the element in the output stream.
randSkipBy :: (a -> Sig) -> Evt a -> Evt a Source #
Skips elements at random.
randSkip probFun
It behaves just like randSkip
, but probability depends on the value.
listAt :: (Tuple a, Arg a) => [a] -> Evt Sig -> Evt a Source #
Turns an event of indices to the event of the values from the list. A value is taken with index.
every :: (Tuple a, Arg a) => Int -> [Int] -> Evt a -> Evt a Source #
Specialization of the function masked
.
every n [a, b, c, ..] evt
constructs a mask that skips first n
elements and then produces
an event and skips next (a - 1) events, then produces an event and
skips next (b - 1) events and so on. It's useful for construction of
the percussive beats. For example
every 0 [2] (metroE 2)
triggers an event on the odd beats. With this function we can create a complex patterns of cyclic events.