csound-expression-typed-0.0.7.1: typed core for the library csound-expression

Safe HaskellNone
LanguageHaskell98

Csound.Typed.Types.Prim

Contents

Synopsis

Documentation

newtype D Source

Constant numbers

Constructors

D 

Fields

unD :: GE E
 

Instances

Floating D 
Fractional D 
Num D 
IfB D 
EqB D 
OrdB D 
Monoid D 
Default D 
SigOrD D 
Val D 
Arg D 
Tuple D 
PureSingle D 
DirtySingle (SE D) 
DirtyMulti b => DirtyMulti ([D] -> b) 
DirtyMulti b => DirtyMulti (D -> b) 
PureMulti b => PureMulti ([D] -> b) 
PureMulti b => PureMulti (D -> b) 
Procedure b => Procedure ([D] -> b) 
Procedure b => Procedure (D -> b) 
DirtySingle b => DirtySingle ([D] -> b) 
DirtySingle b => DirtySingle (D -> b) 
PureSingle b => PureSingle ([D] -> b) 
PureSingle b => PureSingle (D -> b) 
type BooleanOf D = BoolD 
type Snap D = D 

data Tab Source

Tables (or arrays)

Constructors

Tab (GE E) 
TabPre PreTab 

newtype Str Source

Strings

Constructors

Str 

Fields

unStr :: GE E
 

newtype Spec Source

Spectrum. It's fsig in the Csound.

Constructors

Spec 

Fields

unSpec :: GE E
 

newtype Wspec Source

Another type for spectrum. It's wsig in the Csound.

Constructors

Wspec 

Fields

unWspec :: GE E
 

newtype BoolSig Source

A signal of booleans.

Constructors

BoolSig 

Fields

unBoolSig :: GE E
 

newtype BoolD Source

A constant boolean value.

Constructors

BoolD 

Fields

unBoolD :: GE E
 

Instances

newtype Unit Source

Csound's empty tuple.

Constructors

Unit 

Fields

unUnit :: GE ()
 

unit :: Unit Source

Constructs Csound's empty tuple.

class Val a where Source

Contains all Csound values.

Minimal complete definition

fromGE, toGE

Methods

fromGE :: GE E -> a Source

toGE :: a -> GE E Source

fromE :: E -> a Source

hideGE :: Val a => GE a -> a Source

class Val a => SigOrD a Source

Instances

Tables

data TabSize Source

Constructors

SizePlain Int 
SizeDegree 

Instances

fromPreTab :: PreTab -> GE Gen Source

skipNorm :: Tab -> Tab Source

Skips normalization (sets table size to negative value)

forceNorm :: Tab -> Tab Source

Force normalization (sets table size to positive value). Might be useful to restore normalization for table doubles.

nsamp :: Tab -> D Source

nsamp — Returns the number of samples loaded into a stored function table number.

nsamp(x) (init-rate args only)

csound doc: http://www.csounds.com/manual/html/nsamp.html

ftlen :: Tab -> D Source

Returns a length of the table.

ftchnls :: Tab -> D Source

Returns the number of channels for a table that stores wav files

ftsr :: Tab -> D Source

Returns the sample rate for a table that stores wav files

ftcps :: Tab -> D Source

Returns the base frequency for a table that stores wav files

constructors

double :: Double -> D Source

Constructs a number.

int :: Int -> D Source

Constructs an integer.

text :: String -> Str Source

Constructs a string.

constants

idur :: D Source

Querries a total duration of the note. It's equivallent to Csound's p3 field.

converters

ar :: Sig -> Sig Source

Sets a rate of the signal to audio rate.

kr :: Sig -> Sig Source

Sets a rate of the signal to control rate.

ir :: Sig -> D Source

Converts a signal to the number (initial value of the signal).

sig :: D -> Sig Source

Makes a constant signal from the number.

lifters

on0 :: Val a => E -> a Source

on1 :: (Val a, Val b) => (E -> E) -> a -> b Source

on2 :: (Val a, Val b, Val c) => (E -> E -> E) -> a -> b -> c Source

on3 :: (Val a, Val b, Val c, Val d) => (E -> E -> E -> E) -> a -> b -> c -> d Source

numeric funs

quot' :: SigOrD a => a -> a -> a Source

rem' :: SigOrD a => a -> a -> a Source

div' :: SigOrD a => a -> a -> a Source

mod' :: SigOrD a => a -> a -> a Source

ceil' :: SigOrD a => a -> a Source

floor' :: SigOrD a => a -> a Source

round' :: SigOrD a => a -> a Source

int' :: SigOrD a => a -> a Source

frac' :: SigOrD a => a -> a Source

logic funs

when1 :: BoolSig -> SE () -> SE () Source

Invokes the given procedure if the boolean signal is true.

whens :: [(BoolSig, SE ())] -> SE () -> SE () Source

The chain of when1s. Tests all the conditions in sequence if everything is false it invokes the procedure given in the second argument.

untilDo :: BoolSig -> SE () -> SE () Source

whileDo :: BoolSig -> SE () -> SE () Source

boolSig :: BoolD -> BoolSig Source

Creates a constant boolean signal.