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

Safe HaskellNone
LanguageHaskell2010

Csound.Typed.Types.Prim

Contents

Synopsis

Documentation

data Sig Source #

Signals

Constructors

Sig (GE E) 
PrimSig Double 

Instances

Floating Sig Source # 

Methods

pi :: Sig #

exp :: Sig -> Sig #

log :: Sig -> Sig #

sqrt :: Sig -> Sig #

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

logBase :: Sig -> Sig -> Sig #

sin :: Sig -> Sig #

cos :: Sig -> Sig #

tan :: Sig -> Sig #

asin :: Sig -> Sig #

acos :: Sig -> Sig #

atan :: Sig -> Sig #

sinh :: Sig -> Sig #

cosh :: Sig -> Sig #

tanh :: Sig -> Sig #

asinh :: Sig -> Sig #

acosh :: Sig -> Sig #

atanh :: Sig -> Sig #

log1p :: Sig -> Sig #

expm1 :: Sig -> Sig #

log1pexp :: Sig -> Sig #

log1mexp :: Sig -> Sig #

Fractional Sig Source # 

Methods

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

recip :: Sig -> Sig #

fromRational :: Rational -> Sig #

Num Sig Source # 

Methods

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

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

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

negate :: Sig -> Sig #

abs :: Sig -> Sig #

signum :: Sig -> Sig #

fromInteger :: Integer -> Sig #

Monoid Sig Source # 

Methods

mempty :: Sig #

mappend :: Sig -> Sig -> Sig #

mconcat :: [Sig] -> Sig #

IfB Sig Source # 

Methods

ifB :: (* ~ bool) (BooleanOf Sig) => bool -> Sig -> Sig -> Sig #

EqB Sig Source # 

Methods

(==*) :: (* ~ bool) (BooleanOf Sig) => Sig -> Sig -> bool #

(/=*) :: (* ~ bool) (BooleanOf Sig) => Sig -> Sig -> bool #

OrdB Sig Source # 

Methods

(<*) :: (* ~ bool) (BooleanOf Sig) => Sig -> Sig -> bool #

(<=*) :: (* ~ bool) (BooleanOf Sig) => Sig -> Sig -> bool #

(>*) :: (* ~ bool) (BooleanOf Sig) => Sig -> Sig -> bool #

(>=*) :: (* ~ bool) (BooleanOf Sig) => Sig -> Sig -> bool #

Default Sig Source # 

Methods

def :: Sig #

SigOrD Sig Source # 
Val Sig Source # 

Methods

fromGE :: GE E -> Sig Source #

toGE :: Sig -> GE E Source #

fromE :: E -> Sig Source #

Sigs Sig Source # 
Sigs Sig8 Source # 
Sigs Sig6 Source # 
Sigs Sig4 Source # 
Sigs Sig2 Source # 
Tuple Sig Source # 
PureSingle Sig Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> Sig

DirtySingle (SE Sig) Source # 

Methods

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

Sigs (Sig8, Sig8) Source # 
Sigs (Sig2, Sig2) Source # 
DirtyMulti b => DirtyMulti ([Sig] -> b) Source # 

Methods

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

DirtyMulti b => DirtyMulti (Sig -> b) Source # 

Methods

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

PureMulti b => PureMulti ([Sig] -> b) Source # 

Methods

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

PureMulti b => PureMulti (Sig -> b) Source # 

Methods

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

Procedure b => Procedure ([Sig] -> b) Source # 

Methods

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

Procedure b => Procedure (Sig -> b) Source # 

Methods

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

DirtySingle b => DirtySingle ([Sig] -> b) Source # 

Methods

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

DirtySingle b => DirtySingle (Sig -> b) Source # 

Methods

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

PureSingle b => PureSingle ([Sig] -> b) Source # 

Methods

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

PureSingle b => PureSingle (Sig -> b) Source # 

Methods

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

Sigs (Sig2, Sig2, Sig2) Source # 
Sigs (Sig8, Sig8, Sig8, Sig8) Source # 
Sigs (Sig2, Sig2, Sig2, Sig2) Source # 
Sigs (Sig2, Sig2, Sig2, Sig2, Sig2) Source # 
Sigs (Sig2, Sig2, Sig2, Sig2, Sig2, Sig2) Source # 
type BooleanOf Sig Source # 
type Snap Sig Source # 
type Snap Sig = D

data D Source #

Constant numbers

Constructors

D (GE E) 
PrimD Double 

Instances

Floating D Source # 

Methods

pi :: D #

exp :: D -> D #

log :: D -> D #

sqrt :: D -> D #

(**) :: D -> D -> D #

logBase :: D -> D -> D #

sin :: D -> D #

cos :: D -> D #

tan :: D -> D #

asin :: D -> D #

acos :: D -> D #

atan :: D -> D #

sinh :: D -> D #

cosh :: D -> D #

tanh :: D -> D #

asinh :: D -> D #

acosh :: D -> D #

atanh :: D -> D #

log1p :: D -> D #

expm1 :: D -> D #

log1pexp :: D -> D #

log1mexp :: D -> D #

Fractional D Source # 

Methods

(/) :: D -> D -> D #

recip :: D -> D #

fromRational :: Rational -> D #

Num D Source # 

Methods

(+) :: D -> D -> D #

(-) :: D -> D -> D #

(*) :: D -> D -> D #

negate :: D -> D #

abs :: D -> D #

signum :: D -> D #

fromInteger :: Integer -> D #

Monoid D Source # 

Methods

mempty :: D #

mappend :: D -> D -> D #

mconcat :: [D] -> D #

IfB D Source # 

Methods

ifB :: (* ~ bool) (BooleanOf D) => bool -> D -> D -> D #

EqB D Source # 

Methods

(==*) :: (* ~ bool) (BooleanOf D) => D -> D -> bool #

(/=*) :: (* ~ bool) (BooleanOf D) => D -> D -> bool #

OrdB D Source # 

Methods

(<*) :: (* ~ bool) (BooleanOf D) => D -> D -> bool #

(<=*) :: (* ~ bool) (BooleanOf D) => D -> D -> bool #

(>*) :: (* ~ bool) (BooleanOf D) => D -> D -> bool #

(>=*) :: (* ~ bool) (BooleanOf D) => D -> D -> bool #

Default D Source # 

Methods

def :: D #

SigOrD D Source # 
Val D Source # 

Methods

fromGE :: GE E -> D Source #

toGE :: D -> GE E Source #

fromE :: E -> D Source #

Arg D Source # 
Tuple D Source # 
PureSingle D Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> D

DirtySingle (SE D) Source # 

Methods

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

DirtyMulti b => DirtyMulti ([D] -> b) Source # 

Methods

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

DirtyMulti b => DirtyMulti (D -> b) Source # 

Methods

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

PureMulti b => PureMulti ([D] -> b) Source # 

Methods

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

PureMulti b => PureMulti (D -> b) Source # 

Methods

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

Procedure b => Procedure ([D] -> b) Source # 

Methods

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

Procedure b => Procedure (D -> b) Source # 

Methods

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

DirtySingle b => DirtySingle ([D] -> b) Source # 

Methods

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

DirtySingle b => DirtySingle (D -> b) Source # 

Methods

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

PureSingle b => PureSingle ([D] -> b) Source # 

Methods

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

PureSingle b => PureSingle (D -> b) Source # 

Methods

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

type BooleanOf D Source # 
type Snap D Source # 
type Snap D = D

unD :: D -> GE E Source #

data Tab Source #

Tables (or arrays)

Constructors

Tab (GE E) 
TabPre PreTab 

Instances

IfB Tab Source # 

Methods

ifB :: (* ~ bool) (BooleanOf Tab) => bool -> Tab -> Tab -> Tab #

Default Tab Source # 

Methods

def :: Tab #

Val Tab Source # 

Methods

fromGE :: GE E -> Tab Source #

toGE :: Tab -> GE E Source #

fromE :: E -> Tab Source #

Arg Tab Source # 
Tuple Tab Source # 
PureSingle Tab Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> Tab

DirtySingle (SE Tab) Source # 

Methods

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

DirtyMulti b => DirtyMulti (Tab -> b) Source # 

Methods

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

PureMulti b => PureMulti (Tab -> b) Source # 

Methods

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

Procedure b => Procedure (Tab -> b) Source # 

Methods

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

DirtySingle b => DirtySingle (Tab -> b) Source # 

Methods

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

PureSingle b => PureSingle (Tab -> b) Source # 

Methods

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

type BooleanOf Tab Source # 
type Snap Tab Source # 
type Snap Tab = Tab

newtype Str Source #

Strings

Constructors

Str 

Fields

Instances

IfB Str Source # 

Methods

ifB :: (* ~ bool) (BooleanOf Str) => bool -> Str -> Str -> Str #

Default Str Source # 

Methods

def :: Str #

Val Str Source # 

Methods

fromGE :: GE E -> Str Source #

toGE :: Str -> GE E Source #

fromE :: E -> Str Source #

Arg Str Source # 
Tuple Str Source # 
PureSingle Str Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> Str

DirtySingle (SE Str) Source # 

Methods

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

DirtyMulti b => DirtyMulti (Str -> b) Source # 

Methods

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

PureMulti b => PureMulti (Str -> b) Source # 

Methods

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

Procedure b => Procedure (Str -> b) Source # 

Methods

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

DirtySingle b => DirtySingle (Str -> b) Source # 

Methods

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

PureSingle b => PureSingle (Str -> b) Source # 

Methods

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

type BooleanOf Str Source # 
type Snap Str Source # 
type Snap Str = Str

newtype Spec Source #

Spectrum. It's fsig in the Csound.

Constructors

Spec 

Fields

Instances

IfB Spec Source # 

Methods

ifB :: (* ~ bool) (BooleanOf Spec) => bool -> Spec -> Spec -> Spec #

Default Spec Source # 

Methods

def :: Spec #

Val Spec Source # 

Methods

fromGE :: GE E -> Spec Source #

toGE :: Spec -> GE E Source #

fromE :: E -> Spec Source #

Tuple Spec Source # 
PureSingle Spec Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> Spec

DirtySingle (SE Spec) Source # 

Methods

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

DirtyMulti b => DirtyMulti (Spec -> b) Source # 

Methods

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

PureMulti b => PureMulti (Spec -> b) Source # 

Methods

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

Procedure b => Procedure (Spec -> b) Source # 

Methods

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

DirtySingle b => DirtySingle (Spec -> b) Source # 

Methods

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

PureSingle b => PureSingle (Spec -> b) Source # 

Methods

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

type BooleanOf Spec Source # 

newtype Wspec Source #

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

Constructors

Wspec 

Fields

Instances

Val Wspec Source # 

Methods

fromGE :: GE E -> Wspec Source #

toGE :: Wspec -> GE E Source #

fromE :: E -> Wspec Source #

PureSingle Wspec Source # 

Methods

pureSingleGE :: GE ([E] -> E) -> Wspec

DirtySingle (SE Wspec) Source # 

Methods

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

DirtyMulti b => DirtyMulti (Wspec -> b) Source # 

Methods

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

PureMulti b => PureMulti (Wspec -> b) Source # 

Methods

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

Procedure b => Procedure (Wspec -> b) Source # 

Methods

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

DirtySingle b => DirtySingle (Wspec -> b) Source # 

Methods

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

PureSingle b => PureSingle (Wspec -> b) Source # 

Methods

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

data BoolSig Source #

A signal of booleans.

Constructors

BoolSig (GE E) 
PrimBoolSig Bool 

data BoolD Source #

A constant boolean value.

Constructors

BoolD (GE E) 
PrimBoolD Bool 

newtype Unit Source #

Csound's empty tuple.

Constructors

Unit 

Fields

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 (IsPrim a, RealFrac (PrimOf a), 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.

equalsTo :: EqB a => a -> a -> BooleanOf a infix 4 Source #

notEqualsTo :: EqB a => a -> a -> BooleanOf a infix 4 Source #

lessThan :: OrdB a => a -> a -> BooleanOf a infix 4 Source #

greaterThan :: OrdB a => a -> a -> BooleanOf a infix 4 Source #

lessThanEquals :: OrdB a => a -> a -> BooleanOf a infix 4 Source #

greaterThanEquals :: OrdB a => a -> a -> BooleanOf a infix 4 Source #

whenD1 :: BoolD -> SE () -> SE () Source #

Invokes the given procedure if the boolean signal is true.

whenDs :: [(BoolD, 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.

untilDoD :: BoolD -> SE () -> SE () Source #

whileDoD :: BoolD -> SE () -> SE () Source #