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

Safe HaskellNone

Csound.Typed.Types.Prim

Contents

Synopsis

Documentation

newtype Sig Source

Signals

Constructors

Sig 

Fields

unSig :: GE E
 

Instances

Floating Sig 
Fractional Sig 
Num Sig 
Monoid Sig 
Default Sig 
OrdB Sig 
IfB Sig 
EqB Sig 
SigOrD Sig 
Val Sig 
Sigs Sig 
Tuple Sig 
PureSingle Sig 
DirtySingle (SE Sig) 
Sigs ((Sig, Sig, Sig, Sig, Sig, Sig, Sig, Sig), (Sig, Sig, Sig, Sig, Sig, Sig, Sig, Sig)) 
Sigs (Sig, Sig) 
DirtyMulti b => DirtyMulti ([Sig] -> b) 
DirtyMulti b => DirtyMulti (Sig -> b) 
PureMulti b => PureMulti ([Sig] -> b) 
PureMulti b => PureMulti (Sig -> b) 
Procedure b => Procedure ([Sig] -> b) 
Procedure b => Procedure (Sig -> b) 
DirtySingle b => DirtySingle ([Sig] -> b) 
DirtySingle b => DirtySingle (Sig -> b) 
PureSingle b => PureSingle ([Sig] -> b) 
PureSingle b => PureSingle (Sig -> b) 
Sigs ((Sig, Sig, Sig, Sig, Sig, Sig, Sig, Sig), (Sig, Sig, Sig, Sig, Sig, Sig, Sig, Sig), (Sig, Sig, Sig, Sig, Sig, Sig, Sig, Sig), (Sig, Sig, Sig, Sig, Sig, Sig, Sig, Sig)) 
Sigs (Sig, Sig, Sig, Sig) 
Sigs (Sig, Sig, Sig, Sig, Sig, Sig) 
Sigs (Sig, Sig, Sig, Sig, Sig, Sig, Sig, Sig) 

newtype D Source

Constant numbers

Constructors

D 

Fields

unD :: GE E
 

Instances

Floating D 
Fractional D 
Num D 
Monoid D 
Default D 
OrdB D 
IfB D 
EqB 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) 

data Tab Source

Tables (or arrays)

Constructors

Tab (GE E) 
TabPre PreTab 

Instances

Default Tab 
IfB Tab 
Val Tab 
Arg Tab 
Tuple Tab 
PureSingle Tab 
DirtySingle (SE Tab) 
DirtyMulti b => DirtyMulti (Tab -> b) 
PureMulti b => PureMulti (Tab -> b) 
Procedure b => Procedure (Tab -> b) 
DirtySingle b => DirtySingle (Tab -> b) 
PureSingle b => PureSingle (Tab -> b) 

newtype Str Source

Strings

Constructors

Str 

Fields

unStr :: GE E
 

Instances

Default Str 
IfB Str 
Val Str 
Arg Str 
Tuple Str 
PureSingle Str 
DirtySingle (SE Str) 
DirtyMulti b => DirtyMulti (Str -> b) 
PureMulti b => PureMulti (Str -> b) 
Procedure b => Procedure (Str -> b) 
DirtySingle b => DirtySingle (Str -> b) 
PureSingle b => PureSingle (Str -> b) 

newtype Spec Source

Spectrum. It's fsig in the Csound.

Constructors

Spec 

Fields

unSpec :: GE E
 

Instances

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
 

Instances

Boolean BoolSig 
Val BoolSig 

newtype BoolD Source

A constant boolean value.

Constructors

BoolD 

Fields

unBoolD :: GE E
 

Instances

Boolean BoolD 
Val BoolD 

newtype Unit Source

Csound's empty tuple.

Constructors

Unit 

Fields

unUnit :: GE ()
 

Instances

unit :: UnitSource

Constructs Csound's empty tuple.

class Val a whereSource

Contains all Csound values.

Methods

fromGE :: GE E -> aSource

toGE :: a -> GE ESource

fromE :: E -> aSource

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

class Val a => SigOrD a Source

Instances

Tables

data TabSize Source

Constructors

SizePlain Int 
SizeDegree 

Instances

Default TabSize 

fromPreTab :: PreTab -> GE GenSource

skipNorm :: Tab -> TabSource

Skips normalization (sets table size to negative value)

forceNorm :: Tab -> TabSource

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

nsamp :: Tab -> DSource

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 -> DSource

Returns a length of the table.

ftchnls :: Tab -> DSource

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

ftsr :: Tab -> DSource

Returns the sample rate for a table that stores wav files

ftcps :: Tab -> DSource

Returns the base frequency for a table that stores wav files

constructors

double :: Double -> DSource

Constructs a number.

int :: Int -> DSource

Constructs an integer.

text :: String -> StrSource

Constructs a string.

constants

idur :: DSource

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

converters

ar :: Sig -> SigSource

Sets a rate of the signal to audio rate.

kr :: Sig -> SigSource

Sets a rate of the signal to control rate.

ir :: Sig -> DSource

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

sig :: D -> SigSource

Makes a constant signal from the number.

lifters

on0 :: Val a => E -> aSource

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

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

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

numeric funs

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

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

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

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

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

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

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

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

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

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 -> BoolSigSource

Creates a constant boolean signal.