hsc3-0.19.1: 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.

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

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

Type-specialised parse_enum.

mapMaybe (parse_unary Base.CS) (words "Abs Rand_") == [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.

mapMaybe (unaryIndex Base.CI) (words "abs CUBED midicps NEG") == [5,13,17,0]
unaryIndex Base.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.

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

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 #

Type-specialised parse_enum.

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.

mapMaybe (binaryIndex Base.CI) (words "* MUL RING1 +") == [2,2,30,0]
binaryIndex Base.CI "SINOSC" == Nothing
map (\x -> (x,binaryIndex Base.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 Sound.SC3.Common.Base.CI) (words "+ - ADD SUB NEG")

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

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 Integer Source # 
Instance details

Defined in Sound.SC3.Common.Math.Operator

EqE UGen Source # 
Instance details

Defined in Sound.SC3.UGen.Type

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

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 Integer Source # 
Instance details

Defined in Sound.SC3.Common.Math.Operator

OrdE UGen Source # 
Instance details

Defined in Sound.SC3.UGen.Type

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 Double Source # 
Instance details

Defined in Sound.SC3.Common.Math.Operator

UnaryOp Float Source # 
Instance details

Defined in Sound.SC3.Common.Math.Operator

UnaryOp UGen Source # 
Instance details

Defined in Sound.SC3.UGen.Type

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 Double Source # 
Instance details

Defined in Sound.SC3.Common.Math.Operator

BinaryOp Float Source # 
Instance details

Defined in Sound.SC3.Common.Math.Operator

BinaryOp UGen Source # 
Instance details

Defined in Sound.SC3.UGen.Type

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.