hsc3-0.20: Haskell SuperCollider
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sound.Sc3.Common.Math.Operator

Description

Non-standard mathematical enumerations, classes and base instances.

Enumerations of the unary and binary math unit generators. Names that conflict with existing names have a _ suffix.

The Eq and Ord classes in the Prelude require Bool, hence EqE and OrdE. True is 1.0, False is 0.0

The RealFrac class requires Integral results, hence RealFracE.

Synopsis

Unary

data Sc3_Unary_Op Source #

Enumeration of Sc3 unary operator Ugens. The names here are from the enumeration at "serverpluginsUnaryOpUgens.cpp". The capitalisation is edited since these names become function names in rsc3. Names have a _ suffix if they conflict with Ugen names.

zip (map show [minBound :: Sc3_Unary_Op .. maxBound]) [0..]

sc3_unary_op_name :: Sc3_Unary_Op -> String Source #

Enum name without Op prefix.

parse_unary :: Case_Rule -> String -> Maybe Sc3_Unary_Op Source #

parse_enum with Op prefix.

Data.Maybe.mapMaybe (parse_unary Cs) (words "Abs Rand")

sc3_unary_op_tbl :: [(String, Int)] Source #

Table of operator names (non-symbolic) and indices.

map fst sc3_unary_op_tbl

unary_sym_tbl :: [(Sc3_Unary_Op, String)] Source #

Table of symbolic names for standard unary operators.

unaryName :: Int -> String Source #

Lookup possibly symbolic name for standard unary operators.

unaryIndex :: Case_Rule -> String -> Maybe Int Source #

Given name of unary operator derive index.

Data.Maybe.mapMaybe (unaryIndex Ci) (words "abs Cubed midiCps Neg") == [5,13,17,0]
unaryIndex Cs "SinOsc" == Nothing

is_unary :: Case_Rule -> String -> Bool Source #

isJust of unaryIndex.

map (is_unary Ci) (words "Abs MidiCps Neg")
map (is_unary Ci) (words "- rand")
map (is_unary Ci) (words "arctan atan")

Binary

data Sc3_Binary_Op Source #

Enumeration of Sc3 unary operator Ugens. The names here are from the enumeration at "serverpluginsBinaryOpUgens.cpp".

zip (map show [minBound :: Sc3_Binary_Op .. maxBound]) [0..]

sc3_binary_op_name :: Sc3_Binary_Op -> String Source #

Enum name without Op prefix.

sc3_binary_op_tbl :: [(String, Int)] Source #

Table of operator names (non-symbolic) and indices.

parse_binary :: Case_Rule -> String -> Maybe Sc3_Binary_Op Source #

parse_enum with Op prefix.

parse_binary Ci "mul" == Just OpMul

binary_sym_tbl :: [(Sc3_Binary_Op, String)] Source #

Table of symbolic names for standard binary operators.

sc3_binary_op_sym_tbl :: [(String, Int)] Source #

Table of operator names (non-symbolic) and indices.

map fst sc3_binary_op_sym_tbl

binaryName :: Int -> String Source #

Lookup possibly symbolic name for standard binary operators.

map binaryName [1,2,8,12] == ["-","*","<","Min"]

binaryIndex :: Case_Rule -> String -> Maybe Int Source #

Given name of binary operator derive index.

Data.Maybe.mapMaybe (binaryIndex Ci) (words "* mul ring1 +") == [2,2,30,0]
binaryIndex Ci "sinosc" == Nothing
map (\x -> (x,binaryIndex Ci x)) (map snd binary_sym_tbl)

is_binary :: Case_Rule -> String -> Bool Source #

isJust of binaryIndex.

map (is_binary Ci) (words "== > % Trunc max")

Operator

ugen_operator_name :: String -> Int -> Maybe String Source #

Lookup operator name for operator Ugens, else Ugen name.

resolve_operator :: Case_Rule -> String -> (String, Maybe Int) Source #

Order of lookup: binary then unary.

map (resolve_operator Ci) (words "+ - Add sub Neg abs")
map (resolve_operator Cs) (words "Abs")

resolve_operator_ci :: String -> (String, Maybe Int) Source #

Case-insensitive resolve_operator.

Classes

class (Eq a, Num a) => EqE a where Source #

Variant on Eq class, result is of the same type as the values compared.

Minimal complete definition

Nothing

Methods

equal_to :: a -> a -> a Source #

not_equal_to :: a -> a -> a Source #

Instances

Instances details
EqE Int32 Source # 
Instance details

Defined in Sound.Sc3.Common.Math.Operator

EqE Int64 Source # 
Instance details

Defined in Sound.Sc3.Common.Math.Operator

EqE Ugen Source # 
Instance details

Defined in Sound.Sc3.Ugen.Ugen

EqE Integer Source # 
Instance details

Defined in Sound.Sc3.Common.Math.Operator

EqE Double Source # 
Instance details

Defined in Sound.Sc3.Common.Math.Operator

EqE Float Source # 
Instance details

Defined in Sound.Sc3.Common.Math.Operator

EqE Int Source # 
Instance details

Defined in Sound.Sc3.Common.Math.Operator

Methods

equal_to :: Int -> Int -> Int Source #

not_equal_to :: Int -> Int -> Int Source #

class (Ord a, Num a) => OrdE a where Source #

Variant on Ord class, result is of the same type as the values compared.

Minimal complete definition

Nothing

Methods

less_than :: a -> a -> a Source #

less_than_or_equal_to :: a -> a -> a Source #

greater_than :: a -> a -> a Source #

greater_than_or_equal_to :: a -> a -> a Source #

Instances

Instances details
OrdE Int32 Source # 
Instance details

Defined in Sound.Sc3.Common.Math.Operator

OrdE Int64 Source # 
Instance details

Defined in Sound.Sc3.Common.Math.Operator

OrdE Ugen Source # 
Instance details

Defined in Sound.Sc3.Ugen.Ugen

OrdE Integer Source # 
Instance details

Defined in Sound.Sc3.Common.Math.Operator

OrdE Double Source # 
Instance details

Defined in Sound.Sc3.Common.Math.Operator

OrdE Float Source # 
Instance details

Defined in Sound.Sc3.Common.Math.Operator

OrdE Int Source # 
Instance details

Defined in Sound.Sc3.Common.Math.Operator

class RealFrac a => RealFracE a where Source #

Variant of RealFrac with non Integral results.

Minimal complete definition

Nothing

Methods

properFractionE :: a -> (a, a) Source #

truncateE :: a -> a Source #

roundE :: a -> a Source #

ceilingE :: a -> a Source #

floorE :: a -> a Source #

class (Floating a, Ord a) => UnaryOp a where Source #

Unary operator class.

map (floor . (* 1e4) . dbAmp) [-90,-60,-30,0] == [0,10,316,10000]

Minimal complete definition

Nothing

Methods

ampDb :: a -> a Source #

asFloat :: a -> a Source #

asInt :: a -> a Source #

cpsMidi :: a -> a Source #

cpsOct :: a -> a Source #

cubed :: a -> a Source #

dbAmp :: a -> a Source #

distort :: a -> a Source #

frac :: a -> a Source #

isNil :: a -> a Source #

log10 :: a -> a Source #

log2 :: a -> a Source #

midiCps :: a -> a Source #

midiRatio :: a -> a Source #

notE :: a -> a Source #

notNil :: a -> a Source #

octCps :: a -> a Source #

ramp_ :: a -> a Source #

ratioMidi :: a -> a Source #

softClip :: a -> a Source #

squared :: a -> a Source #

Instances

Instances details
UnaryOp Ugen Source # 
Instance details

Defined in Sound.Sc3.Ugen.Ugen

UnaryOp Double Source # 
Instance details

Defined in Sound.Sc3.Common.Math.Operator

UnaryOp Float Source # 
Instance details

Defined in Sound.Sc3.Common.Math.Operator

class (Floating a, RealFrac a, Ord a) => BinaryOp a where Source #

Sc3_Binary_Op operator class.

Minimal complete definition

Nothing

Methods

absDif :: a -> a -> a Source #

amClip :: a -> a -> a Source #

atan2E :: a -> a -> a Source #

clip2 :: a -> a -> a Source #

difSqr :: a -> a -> a Source #

excess :: a -> a -> a Source #

exprandRange :: a -> a -> a Source #

fill :: a -> a -> a Source #

firstArg :: a -> a -> a Source #

fold2 :: a -> a -> a Source #

gcdE :: a -> a -> a Source #

hypot :: a -> a -> a Source #

hypotx :: a -> a -> a Source #

iDiv :: a -> a -> a Source #

lcmE :: a -> a -> a Source #

modE :: a -> a -> a Source #

randRange :: a -> a -> a Source #

ring1 :: a -> a -> a Source #

ring2 :: a -> a -> a Source #

ring3 :: a -> a -> a Source #

ring4 :: a -> a -> a Source #

roundUp :: a -> a -> a Source #

scaleNeg :: a -> a -> a Source #

sqrDif :: a -> a -> a Source #

sqrSum :: a -> a -> a Source #

sumSqr :: a -> a -> a Source #

thresh :: a -> a -> a Source #

trunc :: a -> a -> a Source #

wrap2 :: a -> a -> a Source #

Instances

Instances details
BinaryOp Ugen Source # 
Instance details

Defined in Sound.Sc3.Ugen.Ugen

BinaryOp Double Source # 
Instance details

Defined in Sound.Sc3.Common.Math.Operator

BinaryOp Float Source # 
Instance details

Defined in Sound.Sc3.Common.Math.Operator

Infix

(==**) :: EqE a => a -> a -> a Source #

(/=**) :: EqE a => a -> a -> a Source #

(<**) :: OrdE a => a -> a -> a Source #

(<=**) :: OrdE a => a -> a -> a Source #

(>**) :: OrdE a => a -> a -> a Source #

(>=**) :: OrdE a => a -> a -> a Source #

Tables

binop_hs_tbl :: (Real n, Floating n, RealFrac n) => [(Sc3_Binary_Op, n -> n -> n)] Source #

Association table for Sc3_Binary_Op to haskell function implementing operator.

uop_hs_tbl :: (RealFrac n, Floating n) => [(Sc3_Unary_Op, n -> n)] Source #

Association table for Unary to haskell function implementing operator.