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

Csound.Typed.Control

Synopsis

SE

newtype SE a Source #

The Csound's IO-monad. All values that produce side effects are wrapped in the SE-monad.

Constructors

SE 

Fields

Instances

Instances details
Monad SE Source # 
Instance details

Defined in Csound.Typed.GlobalState.SE

Methods

(>>=) :: SE a -> (a -> SE b) -> SE b #

(>>) :: SE a -> SE b -> SE b #

return :: a -> SE a #

Functor SE Source # 
Instance details

Defined in Csound.Typed.GlobalState.SE

Methods

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

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

Applicative SE Source # 
Instance details

Defined in Csound.Typed.GlobalState.SE

Methods

pure :: a -> SE a #

(<*>) :: SE (a -> b) -> SE a -> SE b #

liftA2 :: (a -> b -> c) -> SE a -> SE b -> SE c #

(*>) :: SE a -> SE b -> SE b #

(<*) :: SE a -> SE b -> SE a #

MixAt Sig2 Sig2 (SE Sig2) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

mixAt :: Sig -> (Sig2 -> Sig2) -> SE Sig2 -> AtOut Sig2 Sig2 (SE Sig2) Source #

MixAt Sig2 Sig2 (SE Sig) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

mixAt :: Sig -> (Sig2 -> Sig2) -> SE Sig -> AtOut Sig2 Sig2 (SE Sig) Source #

MixAt Sig Sig2 (SE Sig2) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

mixAt :: Sig -> (Sig -> Sig2) -> SE Sig2 -> AtOut Sig Sig2 (SE Sig2) Source #

MixAt Sig Sig2 (SE Sig) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

mixAt :: Sig -> (Sig -> Sig2) -> SE Sig -> AtOut Sig Sig2 (SE Sig) Source #

At Sig2 Sig2 (SE Sig2) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Associated Types

type AtOut Sig2 Sig2 (SE Sig2) Source #

Methods

at :: (Sig2 -> Sig2) -> SE Sig2 -> AtOut Sig2 Sig2 (SE Sig2) Source #

At Sig2 Sig2 (SE Sig) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Associated Types

type AtOut Sig2 Sig2 (SE Sig) Source #

Methods

at :: (Sig2 -> Sig2) -> SE Sig -> AtOut Sig2 Sig2 (SE Sig) Source #

At Sig Sig2 (SE Sig2) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Associated Types

type AtOut Sig Sig2 (SE Sig2) Source #

Methods

at :: (Sig -> Sig2) -> SE Sig2 -> AtOut Sig Sig2 (SE Sig2) Source #

At Sig Sig2 (SE Sig) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Associated Types

type AtOut Sig Sig2 (SE Sig) Source #

Methods

at :: (Sig -> Sig2) -> SE Sig -> AtOut Sig Sig2 (SE Sig) Source #

MixAt Sig2 (SE Sig2) Sig2 Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

mixAt :: Sig -> (Sig2 -> SE Sig2) -> Sig2 -> AtOut Sig2 (SE Sig2) Sig2 Source #

MixAt Sig2 (SE Sig2) Sig Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

mixAt :: Sig -> (Sig2 -> SE Sig2) -> Sig -> AtOut Sig2 (SE Sig2) Sig Source #

MixAt Sig (SE Sig) Sig4 Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

mixAt :: Sig -> (Sig -> SE Sig) -> Sig4 -> AtOut Sig (SE Sig) Sig4 Source #

MixAt Sig (SE Sig) Sig3 Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

mixAt :: Sig -> (Sig -> SE Sig) -> Sig3 -> AtOut Sig (SE Sig) Sig3 Source #

MixAt Sig (SE Sig) Sig2 Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

mixAt :: Sig -> (Sig -> SE Sig) -> Sig2 -> AtOut Sig (SE Sig) Sig2 Source #

MixAt Sig (SE Sig) Sig Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

mixAt :: Sig -> (Sig -> SE Sig) -> Sig -> AtOut Sig (SE Sig) Sig Source #

At Sig2 (SE Sig2) Sig2 Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Associated Types

type AtOut Sig2 (SE Sig2) Sig2 Source #

Methods

at :: (Sig2 -> SE Sig2) -> Sig2 -> AtOut Sig2 (SE Sig2) Sig2 Source #

At Sig2 (SE Sig2) Sig Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Associated Types

type AtOut Sig2 (SE Sig2) Sig Source #

Methods

at :: (Sig2 -> SE Sig2) -> Sig -> AtOut Sig2 (SE Sig2) Sig Source #

At Sig (SE Sig) Sig4 Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Associated Types

type AtOut Sig (SE Sig) Sig4 Source #

Methods

at :: (Sig -> SE Sig) -> Sig4 -> AtOut Sig (SE Sig) Sig4 Source #

At Sig (SE Sig) Sig3 Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Associated Types

type AtOut Sig (SE Sig) Sig3 Source #

Methods

at :: (Sig -> SE Sig) -> Sig3 -> AtOut Sig (SE Sig) Sig3 Source #

At Sig (SE Sig) Sig2 Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Associated Types

type AtOut Sig (SE Sig) Sig2 Source #

Methods

at :: (Sig -> SE Sig) -> Sig2 -> AtOut Sig (SE Sig) Sig2 Source #

At Sig (SE Sig) Sig Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Associated Types

type AtOut Sig (SE Sig) Sig Source #

Methods

at :: (Sig -> SE Sig) -> Sig -> AtOut Sig (SE Sig) Sig Source #

MixAt Sig2 (SE Sig2) (SE Sig2) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

mixAt :: Sig -> (Sig2 -> SE Sig2) -> SE Sig2 -> AtOut Sig2 (SE Sig2) (SE Sig2) Source #

MixAt Sig2 (SE Sig2) (SE Sig) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

mixAt :: Sig -> (Sig2 -> SE Sig2) -> SE Sig -> AtOut Sig2 (SE Sig2) (SE Sig) Source #

MixAt Sig2 (SE Sig2) (Sco (Mix Sig2)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Methods

mixAt :: Sig -> (Sig2 -> SE Sig2) -> Sco (Mix Sig2) -> AtOut Sig2 (SE Sig2) (Sco (Mix Sig2)) Source #

MixAt Sig2 (SE Sig2) (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Methods

mixAt :: Sig -> (Sig2 -> SE Sig2) -> Sco (Mix Sig) -> AtOut Sig2 (SE Sig2) (Sco (Mix Sig)) Source #

MixAt Sig (SE Sig2) (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Methods

mixAt :: Sig -> (Sig -> SE Sig2) -> Sco (Mix Sig) -> AtOut Sig (SE Sig2) (Sco (Mix Sig)) Source #

MixAt Sig (SE Sig) (SE Sig4) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

mixAt :: Sig -> (Sig -> SE Sig) -> SE Sig4 -> AtOut Sig (SE Sig) (SE Sig4) Source #

MixAt Sig (SE Sig) (SE Sig3) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

mixAt :: Sig -> (Sig -> SE Sig) -> SE Sig3 -> AtOut Sig (SE Sig) (SE Sig3) Source #

MixAt Sig (SE Sig) (SE Sig2) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

mixAt :: Sig -> (Sig -> SE Sig) -> SE Sig2 -> AtOut Sig (SE Sig) (SE Sig2) Source #

MixAt Sig (SE Sig) (SE Sig) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

mixAt :: Sig -> (Sig -> SE Sig) -> SE Sig -> AtOut Sig (SE Sig) (SE Sig) Source #

MixAt Sig (SE Sig) (Sco (Mix Sig4)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Methods

mixAt :: Sig -> (Sig -> SE Sig) -> Sco (Mix Sig4) -> AtOut Sig (SE Sig) (Sco (Mix Sig4)) Source #

MixAt Sig (SE Sig) (Sco (Mix Sig3)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Methods

mixAt :: Sig -> (Sig -> SE Sig) -> Sco (Mix Sig3) -> AtOut Sig (SE Sig) (Sco (Mix Sig3)) Source #

MixAt Sig (SE Sig) (Sco (Mix Sig2)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Methods

mixAt :: Sig -> (Sig -> SE Sig) -> Sco (Mix Sig2) -> AtOut Sig (SE Sig) (Sco (Mix Sig2)) Source #

MixAt Sig (SE Sig) (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Methods

mixAt :: Sig -> (Sig -> SE Sig) -> Sco (Mix Sig) -> AtOut Sig (SE Sig) (Sco (Mix Sig)) Source #

At Sig2 (SE Sig2) (SE Sig2) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Associated Types

type AtOut Sig2 (SE Sig2) (SE Sig2) Source #

Methods

at :: (Sig2 -> SE Sig2) -> SE Sig2 -> AtOut Sig2 (SE Sig2) (SE Sig2) Source #

At Sig2 (SE Sig2) (SE Sig) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Associated Types

type AtOut Sig2 (SE Sig2) (SE Sig) Source #

Methods

at :: (Sig2 -> SE Sig2) -> SE Sig -> AtOut Sig2 (SE Sig2) (SE Sig) Source #

At Sig2 (SE Sig2) (Sco (Mix Sig2)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Associated Types

type AtOut Sig2 (SE Sig2) (Sco (Mix Sig2)) Source #

Methods

at :: (Sig2 -> SE Sig2) -> Sco (Mix Sig2) -> AtOut Sig2 (SE Sig2) (Sco (Mix Sig2)) Source #

At Sig2 (SE Sig2) (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Associated Types

type AtOut Sig2 (SE Sig2) (Sco (Mix Sig)) Source #

Methods

at :: (Sig2 -> SE Sig2) -> Sco (Mix Sig) -> AtOut Sig2 (SE Sig2) (Sco (Mix Sig)) Source #

At Sig (SE Sig2) (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Associated Types

type AtOut Sig (SE Sig2) (Sco (Mix Sig)) Source #

Methods

at :: (Sig -> SE Sig2) -> Sco (Mix Sig) -> AtOut Sig (SE Sig2) (Sco (Mix Sig)) Source #

At Sig (SE Sig) (SE Sig4) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Associated Types

type AtOut Sig (SE Sig) (SE Sig4) Source #

Methods

at :: (Sig -> SE Sig) -> SE Sig4 -> AtOut Sig (SE Sig) (SE Sig4) Source #

At Sig (SE Sig) (SE Sig3) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Associated Types

type AtOut Sig (SE Sig) (SE Sig3) Source #

Methods

at :: (Sig -> SE Sig) -> SE Sig3 -> AtOut Sig (SE Sig) (SE Sig3) Source #

At Sig (SE Sig) (SE Sig2) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Associated Types

type AtOut Sig (SE Sig) (SE Sig2) Source #

Methods

at :: (Sig -> SE Sig) -> SE Sig2 -> AtOut Sig (SE Sig) (SE Sig2) Source #

At Sig (SE Sig) (SE Sig) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Associated Types

type AtOut Sig (SE Sig) (SE Sig) Source #

Methods

at :: (Sig -> SE Sig) -> SE Sig -> AtOut Sig (SE Sig) (SE Sig) Source #

At Sig (SE Sig) (Sco (Mix Sig4)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Associated Types

type AtOut Sig (SE Sig) (Sco (Mix Sig4)) Source #

Methods

at :: (Sig -> SE Sig) -> Sco (Mix Sig4) -> AtOut Sig (SE Sig) (Sco (Mix Sig4)) Source #

At Sig (SE Sig) (Sco (Mix Sig3)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Associated Types

type AtOut Sig (SE Sig) (Sco (Mix Sig3)) Source #

Methods

at :: (Sig -> SE Sig) -> Sco (Mix Sig3) -> AtOut Sig (SE Sig) (Sco (Mix Sig3)) Source #

At Sig (SE Sig) (Sco (Mix Sig2)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Associated Types

type AtOut Sig (SE Sig) (Sco (Mix Sig2)) Source #

Methods

at :: (Sig -> SE Sig) -> Sco (Mix Sig2) -> AtOut Sig (SE Sig) (Sco (Mix Sig2)) Source #

At Sig (SE Sig) (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Associated Types

type AtOut Sig (SE Sig) (Sco (Mix Sig)) Source #

Methods

at :: (Sig -> SE Sig) -> Sco (Mix Sig) -> AtOut Sig (SE Sig) (Sco (Mix Sig)) Source #

Fractional (SE (Sig, Sig)) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

(/) :: SE (Sig, Sig) -> SE (Sig, Sig) -> SE (Sig, Sig) #

recip :: SE (Sig, Sig) -> SE (Sig, Sig) #

fromRational :: Rational -> SE (Sig, Sig) #

Fractional (SE (Sig, Sig, Sig)) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

(/) :: SE (Sig, Sig, Sig) -> SE (Sig, Sig, Sig) -> SE (Sig, Sig, Sig) #

recip :: SE (Sig, Sig, Sig) -> SE (Sig, Sig, Sig) #

fromRational :: Rational -> SE (Sig, Sig, Sig) #

Fractional (SE (Sig, Sig, Sig, Sig)) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

(/) :: SE (Sig, Sig, Sig, Sig) -> SE (Sig, Sig, Sig, Sig) -> SE (Sig, Sig, Sig, Sig) #

recip :: SE (Sig, Sig, Sig, Sig) -> SE (Sig, Sig, Sig, Sig) #

fromRational :: Rational -> SE (Sig, Sig, Sig, Sig) #

Fractional (SE Sig) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

(/) :: SE Sig -> SE Sig -> SE Sig #

recip :: SE Sig -> SE Sig #

fromRational :: Rational -> SE Sig #

Num (SE (Sig, Sig)) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

(+) :: SE (Sig, Sig) -> SE (Sig, Sig) -> SE (Sig, Sig) #

(-) :: SE (Sig, Sig) -> SE (Sig, Sig) -> SE (Sig, Sig) #

(*) :: SE (Sig, Sig) -> SE (Sig, Sig) -> SE (Sig, Sig) #

negate :: SE (Sig, Sig) -> SE (Sig, Sig) #

abs :: SE (Sig, Sig) -> SE (Sig, Sig) #

signum :: SE (Sig, Sig) -> SE (Sig, Sig) #

fromInteger :: Integer -> SE (Sig, Sig) #

Num (SE (Sig, Sig, Sig)) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

(+) :: SE (Sig, Sig, Sig) -> SE (Sig, Sig, Sig) -> SE (Sig, Sig, Sig) #

(-) :: SE (Sig, Sig, Sig) -> SE (Sig, Sig, Sig) -> SE (Sig, Sig, Sig) #

(*) :: SE (Sig, Sig, Sig) -> SE (Sig, Sig, Sig) -> SE (Sig, Sig, Sig) #

negate :: SE (Sig, Sig, Sig) -> SE (Sig, Sig, Sig) #

abs :: SE (Sig, Sig, Sig) -> SE (Sig, Sig, Sig) #

signum :: SE (Sig, Sig, Sig) -> SE (Sig, Sig, Sig) #

fromInteger :: Integer -> SE (Sig, Sig, Sig) #

Num (SE (Sig, Sig, Sig, Sig)) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

(+) :: SE (Sig, Sig, Sig, Sig) -> SE (Sig, Sig, Sig, Sig) -> SE (Sig, Sig, Sig, Sig) #

(-) :: SE (Sig, Sig, Sig, Sig) -> SE (Sig, Sig, Sig, Sig) -> SE (Sig, Sig, Sig, Sig) #

(*) :: SE (Sig, Sig, Sig, Sig) -> SE (Sig, Sig, Sig, Sig) -> SE (Sig, Sig, Sig, Sig) #

negate :: SE (Sig, Sig, Sig, Sig) -> SE (Sig, Sig, Sig, Sig) #

abs :: SE (Sig, Sig, Sig, Sig) -> SE (Sig, Sig, Sig, Sig) #

signum :: SE (Sig, Sig, Sig, Sig) -> SE (Sig, Sig, Sig, Sig) #

fromInteger :: Integer -> SE (Sig, Sig, Sig, Sig) #

Num (SE Sig) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

(+) :: SE Sig -> SE Sig -> SE Sig #

(-) :: SE Sig -> SE Sig -> SE Sig #

(*) :: SE Sig -> SE Sig -> SE Sig #

negate :: SE Sig -> SE Sig #

abs :: SE Sig -> SE Sig #

signum :: SE Sig -> SE Sig #

fromInteger :: Integer -> SE Sig #

BindSig2 (SE (Sig, Sig)) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

bindSig2 :: (Sig2 -> SE Sig2) -> SE (Sig, Sig) -> SE (SE (Sig, Sig)) Source #

BindSig2 (SE (Sig, Sig, Sig)) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

bindSig2 :: (Sig2 -> SE Sig2) -> SE (Sig, Sig, Sig) -> SE (SE (Sig, Sig, Sig)) Source #

BindSig2 (SE (Sig, Sig, Sig, Sig)) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

bindSig2 :: (Sig2 -> SE Sig2) -> SE (Sig, Sig, Sig, Sig) -> SE (SE (Sig, Sig, Sig, Sig)) Source #

BindSig2 (SE Sig) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

bindSig2 :: (Sig2 -> SE Sig2) -> SE Sig -> SE (SE Sig) Source #

SigSpace2 (SE (Sig, Sig)) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

mapSig2 :: (Sig2 -> Sig2) -> SE (Sig, Sig) -> SE (Sig, Sig) Source #

SigSpace2 (SE (Sig, Sig, Sig)) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

mapSig2 :: (Sig2 -> Sig2) -> SE (Sig, Sig, Sig) -> SE (Sig, Sig, Sig) Source #

SigSpace2 (SE (Sig, Sig, Sig, Sig)) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

mapSig2 :: (Sig2 -> Sig2) -> SE (Sig, Sig, Sig, Sig) -> SE (Sig, Sig, Sig, Sig) Source #

SigSpace2 (SE Sig) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

mapSig2 :: (Sig2 -> Sig2) -> SE Sig -> SE Sig Source #

BindSig a => BindSig (SE a) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

bindSig :: (Sig -> SE Sig) -> SE a -> SE (SE a) Source #

SigSpace a => SigSpace (SE a) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

mapSig :: (Sig -> Sig) -> SE a -> SE a Source #

Procedure (SE ()) Source # 
Instance details

Defined in Csound.Typed.Types.Lift

Methods

procedureGE :: GE ([E] -> Dep ()) -> SE ()

DirtySingle (SE (GE E)) Source # 
Instance details

Defined in Csound.Typed.Types.Lift

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> SE (GE E)

DirtySingle (SE Tab) Source # 
Instance details

Defined in Csound.Typed.Types.Lift

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> SE Tab

DirtySingle (SE Wspec) Source # 
Instance details

Defined in Csound.Typed.Types.Lift

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> SE Wspec

DirtySingle (SE Spec) Source # 
Instance details

Defined in Csound.Typed.Types.Lift

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> SE Spec

DirtySingle (SE Str) Source # 
Instance details

Defined in Csound.Typed.Types.Lift

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> SE Str

DirtySingle (SE D) Source # 
Instance details

Defined in Csound.Typed.Types.Lift

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> SE D

DirtySingle (SE Sig) Source # 
Instance details

Defined in Csound.Typed.Types.Lift

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> SE Sig

Fractional (a -> SE (Sig, Sig, Sig, Sig)) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

(/) :: (a -> SE (Sig, Sig, Sig, Sig)) -> (a -> SE (Sig, Sig, Sig, Sig)) -> a -> SE (Sig, Sig, Sig, Sig) #

recip :: (a -> SE (Sig, Sig, Sig, Sig)) -> a -> SE (Sig, Sig, Sig, Sig) #

fromRational :: Rational -> a -> SE (Sig, Sig, Sig, Sig) #

Fractional (a -> SE (Sig, Sig, Sig)) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

(/) :: (a -> SE (Sig, Sig, Sig)) -> (a -> SE (Sig, Sig, Sig)) -> a -> SE (Sig, Sig, Sig) #

recip :: (a -> SE (Sig, Sig, Sig)) -> a -> SE (Sig, Sig, Sig) #

fromRational :: Rational -> a -> SE (Sig, Sig, Sig) #

Fractional (a -> SE (Sig, Sig)) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

(/) :: (a -> SE (Sig, Sig)) -> (a -> SE (Sig, Sig)) -> a -> SE (Sig, Sig) #

recip :: (a -> SE (Sig, Sig)) -> a -> SE (Sig, Sig) #

fromRational :: Rational -> a -> SE (Sig, Sig) #

Fractional (a -> SE Sig) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

(/) :: (a -> SE Sig) -> (a -> SE Sig) -> a -> SE Sig #

recip :: (a -> SE Sig) -> a -> SE Sig #

fromRational :: Rational -> a -> SE Sig #

Num (a -> SE (Sig, Sig, Sig, Sig)) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

(+) :: (a -> SE (Sig, Sig, Sig, Sig)) -> (a -> SE (Sig, Sig, Sig, Sig)) -> a -> SE (Sig, Sig, Sig, Sig) #

(-) :: (a -> SE (Sig, Sig, Sig, Sig)) -> (a -> SE (Sig, Sig, Sig, Sig)) -> a -> SE (Sig, Sig, Sig, Sig) #

(*) :: (a -> SE (Sig, Sig, Sig, Sig)) -> (a -> SE (Sig, Sig, Sig, Sig)) -> a -> SE (Sig, Sig, Sig, Sig) #

negate :: (a -> SE (Sig, Sig, Sig, Sig)) -> a -> SE (Sig, Sig, Sig, Sig) #

abs :: (a -> SE (Sig, Sig, Sig, Sig)) -> a -> SE (Sig, Sig, Sig, Sig) #

signum :: (a -> SE (Sig, Sig, Sig, Sig)) -> a -> SE (Sig, Sig, Sig, Sig) #

fromInteger :: Integer -> a -> SE (Sig, Sig, Sig, Sig) #

Num (a -> SE (Sig, Sig, Sig)) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

(+) :: (a -> SE (Sig, Sig, Sig)) -> (a -> SE (Sig, Sig, Sig)) -> a -> SE (Sig, Sig, Sig) #

(-) :: (a -> SE (Sig, Sig, Sig)) -> (a -> SE (Sig, Sig, Sig)) -> a -> SE (Sig, Sig, Sig) #

(*) :: (a -> SE (Sig, Sig, Sig)) -> (a -> SE (Sig, Sig, Sig)) -> a -> SE (Sig, Sig, Sig) #

negate :: (a -> SE (Sig, Sig, Sig)) -> a -> SE (Sig, Sig, Sig) #

abs :: (a -> SE (Sig, Sig, Sig)) -> a -> SE (Sig, Sig, Sig) #

signum :: (a -> SE (Sig, Sig, Sig)) -> a -> SE (Sig, Sig, Sig) #

fromInteger :: Integer -> a -> SE (Sig, Sig, Sig) #

Num (a -> SE (Sig, Sig)) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

(+) :: (a -> SE (Sig, Sig)) -> (a -> SE (Sig, Sig)) -> a -> SE (Sig, Sig) #

(-) :: (a -> SE (Sig, Sig)) -> (a -> SE (Sig, Sig)) -> a -> SE (Sig, Sig) #

(*) :: (a -> SE (Sig, Sig)) -> (a -> SE (Sig, Sig)) -> a -> SE (Sig, Sig) #

negate :: (a -> SE (Sig, Sig)) -> a -> SE (Sig, Sig) #

abs :: (a -> SE (Sig, Sig)) -> a -> SE (Sig, Sig) #

signum :: (a -> SE (Sig, Sig)) -> a -> SE (Sig, Sig) #

fromInteger :: Integer -> a -> SE (Sig, Sig) #

Num (a -> SE Sig) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

Methods

(+) :: (a -> SE Sig) -> (a -> SE Sig) -> a -> SE Sig #

(-) :: (a -> SE Sig) -> (a -> SE Sig) -> a -> SE Sig #

(*) :: (a -> SE Sig) -> (a -> SE Sig) -> a -> SE Sig #

negate :: (a -> SE Sig) -> a -> SE Sig #

abs :: (a -> SE Sig) -> a -> SE Sig #

signum :: (a -> SE Sig) -> a -> SE Sig #

fromInteger :: Integer -> a -> SE Sig #

type AtOut Sig2 Sig2 (SE Sig2) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

type AtOut Sig2 Sig2 (SE Sig) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

type AtOut Sig Sig2 (SE Sig2) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

type AtOut Sig Sig2 (SE Sig) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

type AtOut Sig2 (SE Sig2) Sig2 Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

type AtOut Sig2 (SE Sig2) Sig Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

type AtOut Sig (SE Sig) Sig4 Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

type AtOut Sig (SE Sig) Sig3 Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

type AtOut Sig (SE Sig) Sig2 Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

type AtOut Sig (SE Sig) Sig Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

type AtOut Sig (SE Sig) Sig = SE Sig
type AtOut Sig2 (SE Sig2) (SE Sig2) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

type AtOut Sig2 (SE Sig2) (SE Sig2) = SE Sig2
type AtOut Sig2 (SE Sig2) (SE Sig) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

type AtOut Sig2 (SE Sig2) (SE Sig) = SE Sig2
type AtOut Sig2 (SE Sig2) (Sco (Mix Sig2)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

type AtOut Sig2 (SE Sig2) (Sco (Mix Sig2)) = Sco (Mix Sig2)
type AtOut Sig2 (SE Sig2) (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

type AtOut Sig2 (SE Sig2) (Sco (Mix Sig)) = Sco (Mix Sig2)
type AtOut Sig (SE Sig2) (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

type AtOut Sig (SE Sig2) (Sco (Mix Sig)) = Sco (Mix Sig2)
type AtOut Sig (SE Sig) (SE Sig4) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

type AtOut Sig (SE Sig) (SE Sig4) = SE Sig4
type AtOut Sig (SE Sig) (SE Sig3) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

type AtOut Sig (SE Sig) (SE Sig3) = SE Sig3
type AtOut Sig (SE Sig) (SE Sig2) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

type AtOut Sig (SE Sig) (SE Sig2) = SE Sig2
type AtOut Sig (SE Sig) (SE Sig) Source # 
Instance details

Defined in Csound.Typed.Types.SigSpace

type AtOut Sig (SE Sig) (SE Sig) = SE Sig
type AtOut Sig (SE Sig) (Sco (Mix Sig4)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

type AtOut Sig (SE Sig) (Sco (Mix Sig4)) = Sco (Mix Sig4)
type AtOut Sig (SE Sig) (Sco (Mix Sig3)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

type AtOut Sig (SE Sig) (Sco (Mix Sig3)) = Sco (Mix Sig3)
type AtOut Sig (SE Sig) (Sco (Mix Sig2)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

type AtOut Sig (SE Sig) (Sco (Mix Sig2)) = Sco (Mix Sig2)
type AtOut Sig (SE Sig) (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

type AtOut Sig (SE Sig) (Sco (Mix Sig)) = Sco (Mix Sig)

data LocalHistory #

Constructors

LocalHistory 

Instances

Instances details
Default LocalHistory 
Instance details

Defined in Csound.Dynamic.Types.Dep

Methods

def :: LocalHistory #

runSE :: SE a -> GE a Source #

evalSE :: SE a -> GE a Source #

execGEinSE :: SE (GE a) -> SE a Source #

hideGEinDep :: GE (Dep a) -> Dep a Source #

fromDep :: Dep a -> SE (GE a) Source #

fromDep_ :: Dep () -> SE () Source #

geToSe :: GE a -> SE a Source #

newLocalVars :: [Rate] -> GE [E] -> SE [Var] Source #

newGlobalVars :: [Rate] -> GE [E] -> SE [Var] Source #

SE reference

newtype Ref a Source #

It describes a reference to mutable values.

Constructors

Ref [Var] 

writeRef :: Tuple a => Ref a -> a -> SE () Source #

readRef :: Tuple a => Ref a -> SE a Source #

newRef :: Tuple a => a -> SE (Ref a) Source #

Allocates a new local (it is visible within the instrument) mutable value and initializes it with value. A reference can contain a tuple of variables.

mixRef :: (Num a, Tuple a) => Ref a -> a -> SE () Source #

Adds the given signal to the value that is contained in the reference.

modifyRef :: Tuple a => Ref a -> (a -> a) -> SE () Source #

Modifies the Ref value with given function.

sensorsSE :: Tuple a => a -> SE (SE a, a -> SE ()) Source #

An alias for the function newRef. It returns not the reference to mutable value but a pair of reader and writer functions.

newGlobalRef :: Tuple a => a -> SE (Ref a) Source #

Allocates a new global mutable value and initializes it with value. A reference can contain a tuple of variables.

concatRef :: (Tuple a, Tuple b) => Ref a -> Ref b -> Ref (a, b) Source #

concatRef3 :: (Tuple a, Tuple b, Tuple c) => Ref a -> Ref b -> Ref c -> Ref (a, b, c) Source #

concatRef4 :: (Tuple a, Tuple b, Tuple c, Tuple d) => Ref a -> Ref b -> Ref c -> Ref d -> Ref (a, b, c, d) Source #

concatRef5 :: (Tuple a, Tuple b, Tuple c, Tuple d, Tuple e) => Ref a -> Ref b -> Ref c -> Ref d -> Ref e -> Ref (a, b, c, d, e) Source #

newCtrlRef :: Tuple a => a -> SE (Ref a) Source #

Allocates a new local (it is visible within the instrument) mutable value and initializes it with value. A reference can contain a tuple of variables. It contains control signals (k-rate) and constants for numbers (i-rates).

newGlobalCtrlRef :: Tuple a => a -> SE (Ref a) Source #

Allocates a new global mutable value and initializes it with value. A reference can contain a tuple of variables. It contains control signals (k-rate) and constants for numbers (i-rates).

globalSensorsSE :: Tuple a => a -> SE (SE a, a -> SE ()) Source #

An alias for the function newRef. It returns not the reference to mutable value but a pair of reader and writer functions.

newClearableGlobalRef :: Tuple a => a -> SE (Ref a) Source #

Allocates a new clearable global mutable value and initializes it with value. A reference can contain a tuple of variables. The variable is set to zero at the end of every iteration. It's useful for accumulation of audio values from several instruments.

newTab :: D -> SE Tab Source #

Creates a new table. The Tab could be used while the instrument is playing. When the instrument is retriggered the new tab is allocated.

newTab size

newGlobalTab :: Int -> SE Tab Source #

Creates a new global table. It's generated only once. It's persisted between instrument calls.

newGlobalTab identifier size

whileRef :: forall st. Tuple st => st -> (st -> SE BoolSig) -> (st -> SE st) -> SE () Source #

whileRefD :: forall st. Tuple st => st -> (st -> SE BoolD) -> (st -> SE st) -> SE () Source #

Global settings

instr0 :: Tuple a => SE a -> SE a Source #

getIns :: Sigs a => SE a Source #

setDur :: Sigs a => D -> a -> a Source #

Sets the global duration of the file or output signal to the given value. It should be used only once! The proper place is in the top-most expression before sending to dac or writeWav.

Misc

freshId :: SE D Source #

Gets new id.

Score

data Mix a Source #

Special type that represents a scores of sound signals. If an instrument is triggered with the scores the result is wrapped in the value of this type.

Instances

Instances details
MixAt Sig2 Sig2 (Sco (Mix Sig2)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Methods

mixAt :: Sig -> (Sig2 -> Sig2) -> Sco (Mix Sig2) -> AtOut Sig2 Sig2 (Sco (Mix Sig2)) Source #

MixAt Sig2 Sig2 (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Methods

mixAt :: Sig -> (Sig2 -> Sig2) -> Sco (Mix Sig) -> AtOut Sig2 Sig2 (Sco (Mix Sig)) Source #

MixAt Sig Sig2 (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Methods

mixAt :: Sig -> (Sig -> Sig2) -> Sco (Mix Sig) -> AtOut Sig Sig2 (Sco (Mix Sig)) Source #

At Sig2 Sig2 (Sco (Mix Sig2)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Associated Types

type AtOut Sig2 Sig2 (Sco (Mix Sig2)) Source #

Methods

at :: (Sig2 -> Sig2) -> Sco (Mix Sig2) -> AtOut Sig2 Sig2 (Sco (Mix Sig2)) Source #

At Sig2 Sig2 (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Associated Types

type AtOut Sig2 Sig2 (Sco (Mix Sig)) Source #

Methods

at :: (Sig2 -> Sig2) -> Sco (Mix Sig) -> AtOut Sig2 Sig2 (Sco (Mix Sig)) Source #

At Sig Sig2 (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Associated Types

type AtOut Sig Sig2 (Sco (Mix Sig)) Source #

Methods

at :: (Sig -> Sig2) -> Sco (Mix Sig) -> AtOut Sig Sig2 (Sco (Mix Sig)) Source #

MixAt Sig2 (SE Sig2) (Sco (Mix Sig2)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Methods

mixAt :: Sig -> (Sig2 -> SE Sig2) -> Sco (Mix Sig2) -> AtOut Sig2 (SE Sig2) (Sco (Mix Sig2)) Source #

MixAt Sig2 (SE Sig2) (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Methods

mixAt :: Sig -> (Sig2 -> SE Sig2) -> Sco (Mix Sig) -> AtOut Sig2 (SE Sig2) (Sco (Mix Sig)) Source #

MixAt Sig (SE Sig2) (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Methods

mixAt :: Sig -> (Sig -> SE Sig2) -> Sco (Mix Sig) -> AtOut Sig (SE Sig2) (Sco (Mix Sig)) Source #

MixAt Sig (SE Sig) (Sco (Mix Sig4)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Methods

mixAt :: Sig -> (Sig -> SE Sig) -> Sco (Mix Sig4) -> AtOut Sig (SE Sig) (Sco (Mix Sig4)) Source #

MixAt Sig (SE Sig) (Sco (Mix Sig3)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Methods

mixAt :: Sig -> (Sig -> SE Sig) -> Sco (Mix Sig3) -> AtOut Sig (SE Sig) (Sco (Mix Sig3)) Source #

MixAt Sig (SE Sig) (Sco (Mix Sig2)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Methods

mixAt :: Sig -> (Sig -> SE Sig) -> Sco (Mix Sig2) -> AtOut Sig (SE Sig) (Sco (Mix Sig2)) Source #

MixAt Sig (SE Sig) (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Methods

mixAt :: Sig -> (Sig -> SE Sig) -> Sco (Mix Sig) -> AtOut Sig (SE Sig) (Sco (Mix Sig)) Source #

At Sig2 (SE Sig2) (Sco (Mix Sig2)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Associated Types

type AtOut Sig2 (SE Sig2) (Sco (Mix Sig2)) Source #

Methods

at :: (Sig2 -> SE Sig2) -> Sco (Mix Sig2) -> AtOut Sig2 (SE Sig2) (Sco (Mix Sig2)) Source #

At Sig2 (SE Sig2) (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Associated Types

type AtOut Sig2 (SE Sig2) (Sco (Mix Sig)) Source #

Methods

at :: (Sig2 -> SE Sig2) -> Sco (Mix Sig) -> AtOut Sig2 (SE Sig2) (Sco (Mix Sig)) Source #

At Sig (SE Sig2) (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Associated Types

type AtOut Sig (SE Sig2) (Sco (Mix Sig)) Source #

Methods

at :: (Sig -> SE Sig2) -> Sco (Mix Sig) -> AtOut Sig (SE Sig2) (Sco (Mix Sig)) Source #

At Sig (SE Sig) (Sco (Mix Sig4)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Associated Types

type AtOut Sig (SE Sig) (Sco (Mix Sig4)) Source #

Methods

at :: (Sig -> SE Sig) -> Sco (Mix Sig4) -> AtOut Sig (SE Sig) (Sco (Mix Sig4)) Source #

At Sig (SE Sig) (Sco (Mix Sig3)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Associated Types

type AtOut Sig (SE Sig) (Sco (Mix Sig3)) Source #

Methods

at :: (Sig -> SE Sig) -> Sco (Mix Sig3) -> AtOut Sig (SE Sig) (Sco (Mix Sig3)) Source #

At Sig (SE Sig) (Sco (Mix Sig2)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Associated Types

type AtOut Sig (SE Sig) (Sco (Mix Sig2)) Source #

Methods

at :: (Sig -> SE Sig) -> Sco (Mix Sig2) -> AtOut Sig (SE Sig) (Sco (Mix Sig2)) Source #

At Sig (SE Sig) (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Associated Types

type AtOut Sig (SE Sig) (Sco (Mix Sig)) Source #

Methods

at :: (Sig -> SE Sig) -> Sco (Mix Sig) -> AtOut Sig (SE Sig) (Sco (Mix Sig)) Source #

(Sigs a, SigSpace2 a) => SigSpace2 (Sco (Mix a)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Methods

mapSig2 :: (Sig2 -> Sig2) -> Sco (Mix a) -> Sco (Mix a) Source #

(Sigs a, SigSpace a) => SigSpace (Sco (Mix a)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

Methods

mapSig :: (Sig -> Sig) -> Sco (Mix a) -> Sco (Mix a) Source #

type AtOut Sig2 Sig2 (Sco (Mix Sig2)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

type AtOut Sig2 Sig2 (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

type AtOut Sig Sig2 (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

type AtOut Sig Sig2 (Sco (Mix Sig)) = Sco (Mix Sig2)
type AtOut Sig2 (SE Sig2) (Sco (Mix Sig2)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

type AtOut Sig2 (SE Sig2) (Sco (Mix Sig2)) = Sco (Mix Sig2)
type AtOut Sig2 (SE Sig2) (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

type AtOut Sig2 (SE Sig2) (Sco (Mix Sig)) = Sco (Mix Sig2)
type AtOut Sig (SE Sig2) (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

type AtOut Sig (SE Sig2) (Sco (Mix Sig)) = Sco (Mix Sig2)
type AtOut Sig (SE Sig) (Sco (Mix Sig4)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

type AtOut Sig (SE Sig) (Sco (Mix Sig4)) = Sco (Mix Sig4)
type AtOut Sig (SE Sig) (Sco (Mix Sig3)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

type AtOut Sig (SE Sig) (Sco (Mix Sig3)) = Sco (Mix Sig3)
type AtOut Sig (SE Sig) (Sco (Mix Sig2)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

type AtOut Sig (SE Sig) (Sco (Mix Sig2)) = Sco (Mix Sig2)
type AtOut Sig (SE Sig) (Sco (Mix Sig)) Source # 
Instance details

Defined in Csound.Typed.Control.Mix

type AtOut Sig (SE Sig) (Sco (Mix Sig)) = Sco (Mix Sig)

sco :: (Arg a, Sigs b) => (a -> SE b) -> Sco a -> Sco (Mix b) Source #

Plays a bunch of notes with the given instrument.

res = sco instrument scores

eff :: (Sigs a, Sigs b) => (a -> SE b) -> Sco (Mix a) -> Sco (Mix b) Source #

Applies an effect to the sound. Effect is applied to the sound on the give track.

res = eff effect sco
  • effect - a function that takes a tuple of signals and produces a tuple of signals.
  • sco - something that is constructed with sco or eff.

With the function eff you can apply a reverb or adjust the level of the signal. It functions like a mixing board but unlike mixing board it produces the value that you can arrange with functions from your favorite Score-generation library. You can delay it or mix with some other track and apply some another effect on top of it!

mix :: Sigs a => Sco (Mix a) -> a Source #

Renders a scores to the sound signals. we can use it inside the other instruments.

mixBy :: (Arg a, Sigs b) => (a -> Sco (Mix b)) -> a -> b Source #

Imitates a closure for a bunch of notes to be played within another instrument.

monoSco :: forall a. Sigs a => (MonoArg -> SE a) -> Sco (D, D) -> Sco (Mix a) Source #

Plays a bunch of notes with the given monophonic instrument. See details on type MonoArg. The scores contain the pairs of amplitude (0 to 1) and frequency (in Hz).

res = monoSco instrument scores

sco_ :: Arg a => (a -> SE ()) -> Sco a -> Sco (Mix Unit) Source #

Invokes a procedure for the given bunch of events.

mix_ :: Sco (Mix Unit) -> SE () Source #

Converts a bunch of procedures scheduled with scores to a single procedure.

mixBy_ :: Arg a => (a -> Sco (Mix Unit)) -> a -> SE () Source #

Imitates a closure for a bunch of procedures to be played within another instrument.

type Sco a = Track Sig a Source #

type CsdEvent = (Double, Double, Note) #

The Csound note. It's a triple of

(startTime, duration, parameters)

Midi

data Msg Source #

Instances

Instances details
DirtyMulti b => DirtyMulti (Msg -> b) Source # 
Instance details

Defined in Csound.Typed.Types.Lift

Methods

dirtyMultiGE :: GE ([E] -> MultiOut (Dep [E])) -> Msg -> b

PureMulti b => PureMulti (Msg -> b) Source # 
Instance details

Defined in Csound.Typed.Types.Lift

Methods

pureMultiGE :: GE ([E] -> MultiOut [E]) -> Msg -> b

Procedure b => Procedure (Msg -> b) Source # 
Instance details

Defined in Csound.Typed.Types.Lift

Methods

procedureGE :: GE ([E] -> Dep ()) -> Msg -> b

DirtySingle b => DirtySingle (Msg -> b) Source # 
Instance details

Defined in Csound.Typed.Types.Lift

Methods

dirtySingleGE :: GE ([E] -> Dep E) -> Msg -> b

PureSingle b => PureSingle (Msg -> b) Source # 
Instance details

Defined in Csound.Typed.Types.Lift

Methods

pureSingleGE :: GE ([E] -> E) -> Msg -> b

midi :: (Num a, Sigs a) => (Msg -> SE a) -> SE a Source #

Triggers a midi-instrument (aka Csound's massign) for all channels. It's useful to test a single instrument.

midin :: (Num a, Sigs a) => Channel -> (Msg -> SE a) -> SE a Source #

Triggers a midi-instrument (aka Csound's massign) on the specified channel.

pgmidi :: (Num a, Sigs a) => Maybe Int -> Channel -> (Msg -> SE a) -> SE a Source #

Triggers a midi-instrument (aka Csound's pgmassign) on the specified programm bank.

midi_ :: (Msg -> SE ()) -> SE () Source #

Triggers a midi-procedure (aka Csound's massign) for all channels.

midin_ :: Channel -> (Msg -> SE ()) -> SE () Source #

Triggers a midi-procedure (aka Csound's pgmassign) on the given channel.

pgmidi_ :: Maybe Int -> Channel -> (Msg -> SE ()) -> SE () Source #

Triggers a midi-procedure (aka Csound's pgmassign) on the given programm bank.

initMidiCtrl :: D -> D -> D -> SE () Source #

Named instruments (API)

trigByName :: (Arg a, Sigs b) => String -> (a -> SE b) -> SE b Source #

Creates an instrument that can be triggered by name with Csound API. The arguments are determined from the structure of the input for the instrument. If we have a tuple of arguments: (D, D, Tab) The would be rendered to instrument arguments that strts from p4. p1 is the name of teh instrument, p2 is the start time of the note, p3 is the duration of the note. Then p4 and p5 are going to be doubles and p6 is an integer that denotes a functional table.

trigByName_ :: Arg a => String -> (a -> SE ()) -> SE () Source #

Creates an instrument that can be triggered by name with Csound API. The arguments are determined from the structure of the input for the instrument.

With Csound API we can send messages

i "name" time duration arg1 arg2 arg3

trigByNameMidi :: (Arg a, Sigs b) => String -> ((D, D, a) -> SE b) -> SE b Source #

Creates an instrument that can be triggered by name with Csound API.

It's intended to be used like a midi instrument. It simulates a simplified midi protocol. We can trigger notes:

i "givenName" delay duration 1 pitchKey volumeKey auxParams     -- note on
i "givenName" delay duration 0 pitchKey volumeKey auxParams     -- note off

The arguments are

trigByNameMidi name instrument

The instrument takes a triplet of (pitchKey, volumeKey, auxilliaryTuple). The order does matter. Please don't pass the volumeKey as the first argument. The instrument expects the pitch key to be a first argument.

trigByNameMidi_ :: forall a. Arg a => String -> ((D, D, a) -> SE ()) -> SE () Source #

It behaves just like the function trigByNameMidi. Only it doesn't produce an audio signal. It performs some procedure on note on and stops doing the precedure on note off.

OSC

type OscHost = String Source #

The hostname of the computer. An empty string is for local machine.

type OscPort = Int Source #

Port to listen OSC-messages.

type OscAddress = String Source #

Path-like string ("foobar/baz")

type OscType = String Source #

The string specifies the type of expected arguments. The string can contain the characters "bcdfilmst" which stand for Boolean, character, double, float, 32-bit integer, 64-bit integer, MIDI, string and timestamp.

initOsc :: OscPort -> OscRef Source #

Initializes host client. The process starts to run in the background.

listenOsc :: forall a. Tuple a => OscRef -> OscAddress -> OscType -> Evt a Source #

Listens for the OSC-messages. The first argument is OSC-reference. We can create it with the function initOsc. The next two arguments are strings. The former specifies the path-like address to listen the messages. It can be:

/foo/bar/baz

The latter specifies the type of expected arguments. The string can contain the characters "bcdfilmst" which stand for Boolean, character, double, float, 32-bit integer, 64-bit integer, MIDI, string and timestamp.

The result is an event of messages. We can run a callback on it with standard function runEvt:

runEvt :: Evt a -> (a -> SE ()) -> SE ()

sendOsc :: forall a. Tuple a => OscHost -> OscPort -> OscAddress -> OscType -> Evt a -> SE () Source #

Sends OSC-messages. It takes in a name of the host computer (empty string is alocal machine), port on which the target machine is listening, OSC-addres and type. The last argument produces the values for OSC-messages.

class Tuple a => OscVal a Source #

Minimal complete definition

getOscTypes, getOscRef

Instances

Instances details
OscVal Str Source # 
Instance details

Defined in Csound.Typed.Control.Osc

Methods

getOscTypes :: Str -> String

getOscRef :: Str -> SE (Ref Str)

OscVal Sig Source # 
Instance details

Defined in Csound.Typed.Control.Osc

Methods

getOscTypes :: Sig -> String

getOscRef :: Sig -> SE (Ref Sig)

(OscVal a, OscVal b) => OscVal (a, b) Source # 
Instance details

Defined in Csound.Typed.Control.Osc

Methods

getOscTypes :: (a, b) -> String

getOscRef :: (a, b) -> SE (Ref (a, b))

(OscVal a, OscVal b, OscVal c) => OscVal (a, b, c) Source # 
Instance details

Defined in Csound.Typed.Control.Osc

Methods

getOscTypes :: (a, b, c) -> String

getOscRef :: (a, b, c) -> SE (Ref (a, b, c))

(OscVal a, OscVal b, OscVal c, OscVal d) => OscVal (a, b, c, d) Source # 
Instance details

Defined in Csound.Typed.Control.Osc

Methods

getOscTypes :: (a, b, c, d) -> String

getOscRef :: (a, b, c, d) -> SE (Ref (a, b, c, d))

(OscVal a, OscVal b, OscVal c, OscVal d, OscVal e) => OscVal (a, b, c, d, e) Source # 
Instance details

Defined in Csound.Typed.Control.Osc

Methods

getOscTypes :: (a, b, c, d, e) -> String

getOscRef :: (a, b, c, d, e) -> SE (Ref (a, b, c, d, e))

listenOscVal :: (Tuple a, OscVal a) => OscRef -> String -> a -> SE a Source #

Listens for tuples of continuous signals read from OSC-channel.

listenOscVal ref address initValue

Channel

Getters

chnGetD :: Str -> SE D Source #

Reads a value of type double.

chnGetSig :: Str -> SE Sig Source #

Reads an audio signal.

chnGetCtrl :: Str -> SE Sig Source #

Reads a control signal. The control signals are updated at the lower rate.

chnGetStr :: Str -> SE Str Source #

Reads a string.

Setters

chnSetD :: D -> Str -> SE () Source #

Writes a value of type double.

chnSetSig :: Sig -> Str -> SE () Source #

Writes an audio signal.

chnSetCtrl :: Sig -> Str -> SE () Source #

Writes a control signal. The control signals are updated at the lower rate.

chnSetStr :: Str -> Str -> SE () Source #

Writes a string.

Sf2

data Sf Source #

The sf2 sound font preset. It is defined with file name, bank and program integers.

Constructors

Sf 

Fields

SfId (GE E) 

Instances

Instances details
IfB Sf Source # 
Instance details

Defined in Csound.Typed.Control.Sf2

Methods

ifB :: bool ~ BooleanOf Sf => bool -> Sf -> Sf -> Sf #

Default Sf Source # 
Instance details

Defined in Csound.Typed.Control.Sf2

Methods

def :: Sf #

Val Sf Source # 
Instance details

Defined in Csound.Typed.Control.Sf2

Methods

fromGE :: GE E -> Sf Source #

toGE :: Sf -> GE E Source #

fromE :: E -> Sf Source #

type BooleanOf Sf Source # 
Instance details

Defined in Csound.Typed.Control.Sf2

unSf :: Sf -> GE E Source #

Events

sched :: (Arg a, Sigs b) => (a -> SE b) -> Evt (Sco a) -> b Source #

sched_ :: Arg a => (a -> SE ()) -> Evt (Sco a) -> SE () Source #

Triggers a procedure on the event stream.

schedBy :: (Arg a, Sigs b, Arg c) => (a -> SE b) -> (c -> Evt (Sco a)) -> c -> b Source #

A closure to trigger an instrument inside the body of another instrument.

schedHarp :: (Arg a, Sigs b) => D -> (a -> SE b) -> Evt [a] -> b Source #

An instrument is triggered with event stream and delay time is set to zero (event fires immediately) and duration is set to inifinite time. The note is held while the instrument is producing something. If the instrument is silent for some seconds (specified in the first argument) then it's turned off.

schedHarpBy :: (Arg a, Sigs b, Arg c) => D -> (a -> SE b) -> (c -> Evt [a]) -> c -> b Source #

A closure to trigger an instrument inside the body of another instrument.

monoSched :: Evt (Sco (D, D)) -> SE MonoArg Source #

Turns

monoSchedUntil :: Evt (D, D) -> Evt a -> SE MonoArg Source #

Plays the note until next note comes or something happens on the second event stream.

monoSchedHarp :: Evt (D, D) -> SE MonoArg Source #

Plays the note until next note comes

retrigs :: (Arg a, Sigs b) => (a -> SE b) -> Evt [a] -> b Source #

Retriggers an instrument every time an event happens. The note is held until the next event happens.

evtLoop :: (Num a, Tuple a, Sigs a) => Maybe (Evt Unit) -> [SE a] -> [Evt Unit] -> a Source #

evtLoopOnce :: (Num a, Tuple a, Sigs a) => Maybe (Evt Unit) -> [SE a] -> [Evt Unit] -> a Source #

Band-limited oscillators

saw :: Sig -> Sig Source #

A sawtooth.

isaw :: Sig -> Sig Source #

Integrated sawtooth: 4 * x * (1 - x).

pulse :: Sig -> Sig Source #

Pulse (not normalized).

tri :: Sig -> Sig Source #

A triangle wave.

sqr :: Sig -> Sig Source #

A square wave.

blosc :: Tab -> Sig -> Sig Source #

A band-limited oscillator with user defined waveform (it's stored in the table).

saw' :: D -> Sig -> Sig Source #

A sawtooth.

isaw' :: D -> Sig -> Sig Source #

Integrated sawtooth: 4 * x * (1 - x).

pulse' :: D -> Sig -> Sig Source #

Pulse (not normalized).

tri' :: D -> Sig -> Sig Source #

A triangle wave.

sqr' :: D -> Sig -> Sig Source #

A square wave.

blosc' :: Tab -> D -> Sig -> Sig Source #

A band-limited oscillator with user defined waveform (it's stored in the table).

Hard sync

data SyncSmooth Source #

Type of smooth shape to make smooth transitions on retrigger. Available types are:

  • No smooth: RawSync
  • Ramp smooth: SawSync
  • Triangular smooth: TriSync
  • User defined shape: UserSync

Instances

Instances details
Default SyncSmooth Source # 
Instance details

Defined in Csound.Typed.Control.Vco

Methods

def :: SyncSmooth #

sawSync :: Sig -> Sig -> Sig Source #

Sawtooth oscillator with hard-sync. The first argument is a ration between slave and master oscillators.

sawSync ratio cps

isawSync :: Sig -> Sig -> Sig Source #

Integrated sawtooth oscillator with hard-sync. The first argument is a ration between slave and master oscillators.

isawSync ratio cps

pulseSync :: Sig -> Sig -> Sig Source #

Pulse oscillator with hard-sync. The first argument is a ration between slave and master oscillators.

pulseSync ratio cps

triSync :: Sig -> Sig -> Sig Source #

Triangle oscillator with hard-sync. The first argument is a ration between slave and master oscillators.

triSync ratio cps

sqrSync :: Sig -> Sig -> Sig Source #

Square oscillator with hard-sync. The first argument is a ration between slave and master oscillators.

sqrSync ratio cps

bloscSync :: Tab -> Sig -> Sig -> Sig Source #

Band-limited oscillator with hard-sync. The first argument is a ration between slave and master oscillators.

bloscSync tab ratio cps

sawSync' :: D -> Sig -> Sig -> Sig Source #

Sawtooth oscillator with hard-sync with phase. The second argument is a ration between slave and master oscillators.

sawSync' phase ratio cps

isawSync' :: D -> Sig -> Sig -> Sig Source #

Integrated sawtooth oscillator with hard-sync with phase. The second argument is a ration between slave and master oscillators.

isawSync' phase ratio cps

pulseSync' :: D -> Sig -> Sig -> Sig Source #

Pulse oscillator with hard-sync with phase. The second argument is a ration between slave and master oscillators.

pulseSync' phase ratio cps

triSync' :: D -> Sig -> Sig -> Sig Source #

Triangle oscillator with hard-sync with phase. The second argument is a ration between slave and master oscillators.

triSync' phase ratio cps

sqrSync' :: D -> Sig -> Sig -> Sig Source #

Square oscillator with hard-sync with phase. The second argument is a ration between slave and master oscillators.

sqrSync' phase ratio cps

bloscSync' :: Tab -> D -> Sig -> Sig -> Sig Source #

Band-limited oscillator with hard-sync with phase. The second argument is a ration between slave and master oscillators.

bloscSync' phase tab ratio cps

Hard sync with absolute frequency for slave oscillator

sawSyncAbs :: Sig -> Sig -> Sig Source #

Sawtooth oscillator with hard-sync. The freq argument is an absolute frequency of a slave oscillator.

sawSyncAbs freq slaveCps masterCps

isawSyncAbs :: Sig -> Sig -> Sig Source #

Integrated sawtooth oscillator with hard-sync. The freq argument is an absolute frequency of a slave oscillator.

isawSyncAbs freq slaveCps masterCps

pulseSyncAbs :: Sig -> Sig -> Sig Source #

Pulse oscillator with hard-sync. The freq argument is an absolute frequency of a slave oscillator.

pulseSyncAbs freq slaveCps masterCps

triSyncAbs :: Sig -> Sig -> Sig Source #

Triangle oscillator with hard-sync. The freq argument is an absolute frequency of a slave oscillator.

triSyncAbs freq slaveCps masterCps

sqrSyncAbs :: Sig -> Sig -> Sig Source #

Square oscillator with hard-sync. The freq argument is an absolute frequency of a slave oscillator.

sqrSyncAbs freq slaveCps masterCps

bloscSyncAbs :: Tab -> Sig -> Sig -> Sig Source #

Bandlimited table oscillator with hard-sync. The freq argument is an absolute frequency of a slave oscillator.

bloscSyncAbs tab freq slaveCps masterCps

sawSyncAbs' :: D -> Sig -> Sig -> Sig Source #

Sawtooth oscillator with hard-sync with phase. The freq argument is an absolute frequency of a slave oscillator.

sawSyncAbs' phase freq slaveCps masterCps

isawSyncAbs' :: D -> Sig -> Sig -> Sig Source #

Integrated sawtooth oscillator with hard-sync with phase. The freq argument is an absolute frequency of a slave oscillator.

isawSyncAbs' phase freq slaveCps masterCps

pulseSyncAbs' :: D -> Sig -> Sig -> Sig Source #

Pulse oscillator with hard-sync with phase. The freq argument is an absolute frequency of a slave oscillator.

pulseSyncAbs' phase freq slaveCps masterCps

triSyncAbs' :: D -> Sig -> Sig -> Sig Source #

Triangle oscillator with hard-sync with phase. The freq argument is an absolute frequency of a slave oscillator.

triSyncAbs' phase freq slaveCps masterCps

sqrSyncAbs' :: D -> Sig -> Sig -> Sig Source #

Square oscillator with hard-sync with phase. The freq argument is an absolute frequency of a slave oscillator.

sqrSyncAbs' phase freq slaveCps masterCps

bloscSyncAbs' :: Tab -> D -> Sig -> Sig -> Sig Source #

Bandlimited table oscillator with hard-sync with phase. The freq argument is an absolute frequency of a slave oscillator.

bloscSyncAbs' phase tab freq slaveCps masterCps

Hard sync with custom smoothing algorythm

sawSyncBy :: SyncSmooth -> Sig -> Sig -> Sig Source #

Sawtooth oscillator with hard-sync. We can specify the smoothness type. The ratio argument is a ration between slave and master oscillators.

sawSyncBy spec ratio cps

isawSyncBy :: SyncSmooth -> Sig -> Sig -> Sig Source #

Integrated sawtooth oscillator with hard-sync. We can specify the smoothness type. The first argument is a ration between slave and master oscillators.

isawSyncB specy ratio cps

pulseSyncBy :: SyncSmooth -> Sig -> Sig -> Sig Source #

Pulse oscillator with hard-sync. We can specify the smoothness type. The ratio argument is a ration between slave and master oscillators.

pulseSyncBy spec ratio cps

triSyncBy :: SyncSmooth -> Sig -> Sig -> Sig Source #

Triangle oscillator with hard-sync. We can specify the smoothness type. The ratio argument is a ration between slave and master oscillators.

triSyncBy spec ratio cps

sqrSyncBy :: SyncSmooth -> Sig -> Sig -> Sig Source #

Square oscillator with hard-sync. We can specify the smoothness type. The ratio argument is a ration between slave and master oscillators.

sawSyncBy spec ratio cps

bloscSyncBy :: SyncSmooth -> Tab -> Sig -> Sig -> Sig Source #

Bandlimited table oscillator with hard-sync. We can specify the smoothness type. The ratio argument is a ration between slave and master oscillators.

bloscSyncBy spec tab ratio cps

sawSyncBy' :: SyncSmooth -> D -> Sig -> Sig -> Sig Source #

Sawtooth oscillator with hard-sync with phase. We can specify the smoothness type. The ratio argument is a ration between slave and master oscillators.

sawSyncBy' spec phase ratio cps

isawSyncBy' :: SyncSmooth -> D -> Sig -> Sig -> Sig Source #

Integrated sawtooth oscillator with hard-sync with phase. We can specify the smoothness type. The ratio argument is a ration between slave and master oscillators.

isawSyncBy' spec phase ratio cps

pulseSyncBy' :: SyncSmooth -> D -> Sig -> Sig -> Sig Source #

Pulse oscillator with hard-sync with phase. We can specify the smoothness type. The ratio argument is a ration between slave and master oscillators.

pulseSyncBy' spec phase ratio cps

triSyncBy' :: SyncSmooth -> D -> Sig -> Sig -> Sig Source #

Triangle oscillator with hard-sync with phase. We can specify the smoothness type. The ratio argument is a ration between slave and master oscillators.

triSyncBy' spec phase ratio cps

sqrSyncBy' :: SyncSmooth -> D -> Sig -> Sig -> Sig Source #

Square oscillator with hard-sync with phase. We can specify the smoothness type. The ratio argument is a ration between slave and master oscillators.

sawSyncBy' spec phase ratio cps

bloscSyncBy' :: SyncSmooth -> Tab -> D -> Sig -> Sig -> Sig Source #

Bandlimited table oscillator with hard-sync with phase. We can specify the smoothness type. The ratio argument is a ration between slave and master oscillators.

bloscSyncBy' spec phase tab ratio cps

Hard sync with absolute frequency for slave oscillator

sawSyncAbsBy :: SyncSmooth -> Sig -> Sig -> Sig Source #

A hard sync for sawtooth with absolute slave frequency.

sawSyncAbs syncType salveCps masterCps

isawSyncAbsBy :: SyncSmooth -> Sig -> Sig -> Sig Source #

A hard sync for integrated sawtooth: 4 * x * (1 - x) with absolute slave frequency.

isawSyncAbs syncType salveCps masterCps

pulseSyncAbsBy :: SyncSmooth -> Sig -> Sig -> Sig Source #

A hard sync for pulse wave with absolute slave frequency.

pulseSyncAbs syncType salveCps masterCps

triSyncAbsBy :: SyncSmooth -> Sig -> Sig -> Sig Source #

A hard sync for triangle wave with absolute slave frequency.

triSyncAbs syncType salveCps masterCps

sqrSyncAbsBy :: SyncSmooth -> Sig -> Sig -> Sig Source #

A hard sync for square wave with absolute slave frequency.

sqrSyncAbs syncType salveCps masterCps

bloscSyncAbsBy :: SyncSmooth -> Tab -> Sig -> Sig -> Sig Source #

A hard sync for band-limited oscillator with user defined waveform (it's stored in the table) woth absolute frequency.

bloscSyncAbs syncType ftable salveCps masterCps

sawSyncAbsBy' :: SyncSmooth -> D -> Sig -> Sig -> Sig Source #

A sawtooth.

isawSyncAbsBy' :: SyncSmooth -> D -> Sig -> Sig -> Sig Source #

Integrated sawtooth: 4 * x * (1 - x).

pulseSyncAbsBy' :: SyncSmooth -> D -> Sig -> Sig -> Sig Source #

Pulse (not normalized).

triSyncAbsBy' :: SyncSmooth -> D -> Sig -> Sig -> Sig Source #

A triangle wave.

sqrSyncAbsBy' :: SyncSmooth -> D -> Sig -> Sig -> Sig Source #

A square wave.

bloscSyncAbsBy' :: SyncSmooth -> Tab -> D -> Sig -> Sig -> Sig Source #

A band-limited oscillator with user defined waveform (it's stored in the table).

Imperative instruments

data InstrRef a Source #

Instrument reference. we can invoke or stop the instrument by the identifier.

newInstr :: Arg a => (a -> SE ()) -> SE (InstrRef a) Source #

Creates a new instrument and generates a unique identifier.

scheduleEvent :: Arg a => InstrRef a -> D -> D -> a -> SE () Source #

Schedules an event for the instrument.

scheduleEvent instrRef delay duration args

The arguments for time values are set in seconds.

turnoff2 :: InstrRef a -> Sig -> Sig -> SE () Source #

Turns off the note played on the given instrument. Use fractional instrument reference to turn off specific instance.

turnoff2 instrRef mode releaseTime

The mode is sum of the following values:

  • 0, 1, or 2: turn off all instances (0), oldest only (1), or newest only (2)
  • 4: only turn off notes with exactly matching (fractional) instrument number, rather than ignoring fractional part
  • 8: only turn off notes with indefinite duration (idur < 0 or MIDI)

releaseTime if non-zero, the turned off instances are allowed to release, otherwise are deactivated immediately (possibly resulting in clicks).

negateInstrRef :: InstrRef a -> InstrRef a Source #

Negates the instrument identifier. This trick is used in Csound to update the instrument arguments while instrument is working.

addFracInstrRef :: D -> D -> InstrRef a -> InstrRef a Source #

Adds fractional part to the instrument reference. This trick is used in Csound to identify the notes (or specific instrument invokation).

newOutInstr :: (Arg a, Sigs b) => (a -> SE b) -> SE (InstrRef a, b) Source #

Creates an insturment that produces a value.

noteOn :: Arg a => D -> D -> InstrRef a -> a -> SE () Source #

Triggers a note with fractional instrument reference. We can later stop the instrument on specific note with function noteOff.

noteOff :: (Default a, Arg a) => D -> D -> InstrRef a -> SE () Source #

Stops a note with fractional instrument reference.

Array folding and traversals

foreachArr :: (Tuple ix, Tuple a) => Arr ix a -> ((ix, a) -> SE ()) -> SE () Source #

Traverses all elements of the array array and applies a procedure to each element. The procedure takes in a pair of index and the current value at the given index.

foreachArrD :: (Tuple ix, Tuple a) => Arr ix a -> ((ix, a) -> SE ()) -> SE () Source #

Traverses all elements of the array at the **init rate** and applies a procedure to each element. The procedure takes in a pair of index and the current value at the given index.

forRowArr :: Tuple a => Sig -> Arr Sig2 a -> ((Sig, a) -> SE ()) -> SE () Source #

Traverses all elements in the given row of 2D array at the signal rate and applies a procedure to all elements.

forColumnArr :: Tuple a => Sig -> Arr Sig2 a -> ((Sig, a) -> SE ()) -> SE () Source #

Traverses all elements in the given column of 2D array at the signal rate and applies a procedure to all elements.

forRowArrD :: Tuple a => D -> Arr D2 a -> ((D, a) -> SE ()) -> SE () Source #

Traverses all elements in the given row of 2D array at the init rate and applies a procedure to all elements.

forColumnArrD :: Tuple a => D -> Arr D2 a -> ((D, a) -> SE ()) -> SE () Source #

Traverses all elements in the given column of 2D array at the init rate and applies a procedure to all elements.

foldArr :: (Tuple ix, Tuple a, Tuple b) => ((ix, a) -> b -> SE b) -> b -> Arr ix a -> SE b Source #

Traverses an array and accumulates a value. We invoke the function with accumulator function, initial value and the array.

foldRowArr :: (Tuple a, Tuple b) => ((Sig, a) -> b -> SE b) -> b -> Sig -> Arr Sig2 a -> SE b Source #

Traverses a row in the array and accumulates a value. We invoke the function with accumulator function, initial value and the array with signal of the row number.

foldRowArr accum initValue rowId array

foldColumnArr :: (Tuple a, Tuple b) => ((Sig, a) -> b -> SE b) -> b -> Sig -> Arr Sig2 a -> SE b Source #

Traverses a column in the array and accumulates a value. We invoke the function with accumulator function, initial value and the array with signal of the row number.

foldColumnArr accum initValue columnId array

foldRowsArrD :: (Tuple a, Tuple b) => ((D, a) -> b -> SE b) -> b -> D -> Arr D2 a -> SE b Source #

Traverses a row at the **init rate** in the array and accumulates a value. We invoke the function with accumulator function, initial value and the array with signal of the row number.

foldRowArr accum initValue rowId array

foldColumnsArrD :: (Tuple a, Tuple b) => ((D, a) -> b -> SE b) -> b -> D -> Arr D2 a -> SE b Source #

Traverses a column at the **init rate** in the array and accumulates a value. We invoke the function with accumulator function, initial value and the array with signal of the row number.

foldColumnArr accum initValue columnId array

Reads global config arguments from command line