hsc3-0.20: Haskell SuperCollider
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sound.Sc3.Common.Mce

Description

The Sc3 multiple channel expansion (Mce) rules over an abstract type.

Synopsis

Documentation

data Mce t Source #

Multiple channel expansion. The Mce type is a tree, however in hsc3 Mce_Vector will always hold Mce_Scalar elements.

Constructors

Mce_Scalar t 
Mce_Vector [Mce t] 

Instances

Instances details
Functor Mce Source # 
Instance details

Defined in Sound.Sc3.Common.Mce

Methods

fmap :: (a -> b) -> Mce a -> Mce b #

(<$) :: a -> Mce b -> Mce a #

Floating n => Floating (Mce n) Source # 
Instance details

Defined in Sound.Sc3.Common.Mce

Methods

pi :: Mce n #

exp :: Mce n -> Mce n #

log :: Mce n -> Mce n #

sqrt :: Mce n -> Mce n #

(**) :: Mce n -> Mce n -> Mce n #

logBase :: Mce n -> Mce n -> Mce n #

sin :: Mce n -> Mce n #

cos :: Mce n -> Mce n #

tan :: Mce n -> Mce n #

asin :: Mce n -> Mce n #

acos :: Mce n -> Mce n #

atan :: Mce n -> Mce n #

sinh :: Mce n -> Mce n #

cosh :: Mce n -> Mce n #

tanh :: Mce n -> Mce n #

asinh :: Mce n -> Mce n #

acosh :: Mce n -> Mce n #

atanh :: Mce n -> Mce n #

log1p :: Mce n -> Mce n #

expm1 :: Mce n -> Mce n #

log1pexp :: Mce n -> Mce n #

log1mexp :: Mce n -> Mce n #

Num n => Num (Mce n) Source # 
Instance details

Defined in Sound.Sc3.Common.Mce

Methods

(+) :: Mce n -> Mce n -> Mce n #

(-) :: Mce n -> Mce n -> Mce n #

(*) :: Mce n -> Mce n -> Mce n #

negate :: Mce n -> Mce n #

abs :: Mce n -> Mce n #

signum :: Mce n -> Mce n #

fromInteger :: Integer -> Mce n #

Read t => Read (Mce t) Source # 
Instance details

Defined in Sound.Sc3.Common.Mce

Fractional n => Fractional (Mce n) Source # 
Instance details

Defined in Sound.Sc3.Common.Mce

Methods

(/) :: Mce n -> Mce n -> Mce n #

recip :: Mce n -> Mce n #

fromRational :: Rational -> Mce n #

Show t => Show (Mce t) Source # 
Instance details

Defined in Sound.Sc3.Common.Mce

Methods

showsPrec :: Int -> Mce t -> ShowS #

show :: Mce t -> String #

showList :: [Mce t] -> ShowS #

Eq t => Eq (Mce t) Source # 
Instance details

Defined in Sound.Sc3.Common.Mce

Methods

(==) :: Mce t -> Mce t -> Bool #

(/=) :: Mce t -> Mce t -> Bool #

Ord t => Ord (Mce t) Source # 
Instance details

Defined in Sound.Sc3.Common.Mce

Methods

compare :: Mce t -> Mce t -> Ordering #

(<) :: Mce t -> Mce t -> Bool #

(<=) :: Mce t -> Mce t -> Bool #

(>) :: Mce t -> Mce t -> Bool #

(>=) :: Mce t -> Mce t -> Bool #

max :: Mce t -> Mce t -> Mce t #

min :: Mce t -> Mce t -> Mce t #

mce_is_well_formed :: Mce t -> Bool Source #

There are two invariants: 1. Mce should not be empty, ie. Mce_Vector should not have a null list. 2. Scalar Mce values should not be written as one-place vectors.

mce_is_well_formed (Mce_Vector []) == False
mce_is_well_formed (Mce_Vector [Mce_Scalar 1]) == False

mce_is_scalar :: Mce t -> Bool Source #

Is Mce scalar.

mce_from_list :: [t] -> Mce t Source #

fromList for Mce, generates well-formed Mce.

mce_to_list :: Mce t -> [t] Source #

toList for Mce.

let v = Mce_Vector in mce_to_list (v[v[1, 2], 3, v[4, 5]]) == [1, 2, 3, 4, 5]

mce_show :: Show t => Mce t -> String Source #

Pretty printer for Mce.

let v = Mce_Vector in mce_show (v[1, 2, v[3, 4]] * 5 + v[6, 7, 8]) == "[11, 17, [23, 28]]"

mce_scalar_value :: Mce t -> t Source #

Read value from Mce_Scalar, error if Mce is Mce_Vector

mce_length :: Mce a -> Int Source #

Length, or perhaps rather width, of Mce. Considers only the outermost level, i.e. mce_length is not necessarily the length of mce_to_list.

mce_depth :: Mce a -> Int Source #

The depth of an Mce is the longest sequence of nested Mce_Vector nodes.

mce_depth 1 == 1
mce_depth (Mce_Vector [1, 2]) == 1
let v = Mce_Vector in mce_depth (v[v[1, 2], 3, v[4, 5]]) == 2
let v = Mce_Vector in mce_depth (v[v[1, 2, 3, v[4, 5], 6], 7]) == 3

mce_extend :: Int -> Mce t -> Mce t Source #

Extend Mce to specified degree. Considers only the outermost level.

mce_map :: (a -> b) -> Mce a -> Mce b Source #

fmap for Mce, apply f at elements of m.

mce_binop :: (a -> b -> c) -> Mce a -> Mce b -> Mce c Source #

Apply f pairwise at elements of m1 and m2. At each level this extends the shorter of the two operands.