csound-expression-typed-0.2.4: typed core for the library csound-expression
Safe HaskellNone
LanguageHaskell2010

Csound.Typed.Types.Evt

Synopsis

Documentation

data Evt a Source #

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.

Constructors

Evt 

Fields

Instances

Instances details
Functor Evt Source # 
Instance details

Defined in Csound.Typed.Types.Evt

Methods

fmap :: (a -> b) -> Evt a -> Evt b #

(<$) :: a -> Evt b -> Evt a #

Semigroup (Evt a) Source # 
Instance details

Defined in Csound.Typed.Types.Evt

Methods

(<>) :: Evt a -> Evt a -> Evt a #

sconcat :: NonEmpty (Evt a) -> Evt a #

stimes :: Integral b => b -> Evt a -> Evt a #

Monoid (Evt a) Source # 
Instance details

Defined in Csound.Typed.Types.Evt

Methods

mempty :: Evt a #

mappend :: Evt a -> Evt a -> Evt a #

mconcat :: [Evt a] -> Evt a #

Default (Evt a) Source # 
Instance details

Defined in Csound.Typed.Types.Evt

Methods

def :: Evt a #

type Bam a = a -> SE () Source #

A procedure. Something that takes a value and suddenly bams with it.

sync :: (Default a, Tuple a) => Sig -> Evt a -> Evt a Source #

Executes actions synchronized with global tempo (in Hz).

runEvtSync tempoCps evt proc

boolToEvt :: BoolSig -> Evt Unit Source #

Converts booleans to events.

evtToBool :: Evt a -> SE BoolSig Source #

Converts an event to boolean signal. It forgets everything about the event values. Signal equals to one when an event happens and zero otherwise.

sigToEvt :: Sig -> Evt Unit Source #

Triggers an event when signal equals to 1.

stepper :: Tuple a => a -> Evt a -> SE a Source #

Converts events to signals.

filterE :: (a -> BoolD) -> Evt a -> Evt a Source #

Filters events with predicate.

filterSE :: (a -> SE BoolD) -> Evt a -> Evt a Source #

Filters events with effectful predicate.

accumSE :: Tuple s => s -> (a -> s -> SE (b, s)) -> Evt a -> Evt b Source #

Accumulator for events with side effects.

accumE :: Tuple s => s -> (a -> s -> (b, s)) -> Evt a -> Evt b Source #

Accumulator for events.

filterAccumE :: Tuple s => s -> (a -> s -> (BoolD, b, s)) -> Evt a -> Evt b Source #

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 (BoolD, b, s)) -> Evt a -> Evt b Source #

Accumulator for events with side effects and filtering. Event triggers only if the first element in the tripplet is true.

type family Snap a :: * Source #

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

Instances details
type Snap Tab Source # 
Instance details

Defined in Csound.Typed.Types.Evt

type Snap Tab = Tab
type Snap Str Source # 
Instance details

Defined in Csound.Typed.Types.Evt

type Snap Str = Str
type Snap D Source # 
Instance details

Defined in Csound.Typed.Types.Evt

type Snap D = D
type Snap Sig Source # 
Instance details

Defined in Csound.Typed.Types.Evt

type Snap Sig = D
type Snap (a, b) Source # 
Instance details

Defined in Csound.Typed.Types.Evt

type Snap (a, b) = (Snap a, Snap b)
type Snap (a, b, c) Source # 
Instance details

Defined in Csound.Typed.Types.Evt

type Snap (a, b, c) = (Snap a, Snap b, Snap c)
type Snap (a, b, c, d) Source # 
Instance details

Defined in Csound.Typed.Types.Evt

type Snap (a, b, c, d) = (Snap a, Snap b, Snap c, Snap d)
type Snap (a, b, c, d, e) Source # 
Instance details

Defined in Csound.Typed.Types.Evt

type Snap (a, b, c, d, e) = (Snap a, Snap b, Snap c, Snap d, Snap e)
type Snap (a, b, c, d, e, f) Source # 
Instance details

Defined in Csound.Typed.Types.Evt

type Snap (a, b, c, d, e, f) = (Snap a, Snap b, Snap c, Snap d, Snap e, Snap f)

snapshot :: (Tuple a, Tuple (Snap a)) => (Snap a -> b -> c) -> a -> Evt b -> Evt c Source #

Get values of some signal at the given events.

snaps :: Sig -> Evt D Source #

Constructs an event stream that contains values from the given signal. Events happens only when the signal changes.

readSnap :: (Tuple (Snap a), Tuple a) => a -> Snap a Source #