AlgoRhythm-0.1.0.0: Algorithmic music composition

Safe HaskellSafe
LanguageHaskell2010

Music.Transformations

Contents

Synopsis

Documentation

class Transposable a where Source #

Operator precedence.

Anything that can be transposed with an Interval.

Minimal complete definition

trans, trans_, snart, snart_

Methods

trans, trans_, snart, snart_ :: Interval -> a -> a Source #

(~>), (<~), (~~>), (<~~) :: a -> Interval -> a infixl 5 ~>, <~, ~~>, <~~ Source #

Instances

BoundEnum a => Transposable a Source # 

Methods

trans :: Interval -> a -> a Source #

trans_ :: Interval -> a -> a Source #

snart :: Interval -> a -> a Source #

snart_ :: Interval -> a -> a Source #

(~>) :: a -> Interval -> a Source #

(<~) :: a -> Interval -> a Source #

(~~>) :: a -> Interval -> a Source #

(<~~) :: a -> Interval -> a Source #

Transposable FullPitch Source # 
Transposable a => Transposable [a] Source # 

Methods

trans :: Interval -> [a] -> [a] Source #

trans_ :: Interval -> [a] -> [a] Source #

snart :: Interval -> [a] -> [a] Source #

snart_ :: Interval -> [a] -> [a] Source #

(~>) :: [a] -> Interval -> [a] Source #

(<~) :: [a] -> Interval -> [a] Source #

(~~>) :: [a] -> Interval -> [a] Source #

(<~~) :: [a] -> Interval -> [a] Source #

Transposable a => Transposable (Music a) Source # 

class Invertible f a where Source #

Minimal complete definition

invert

Methods

invert :: f a -> f a Source #

invertN :: Int -> f a -> f a Source #

Instances

Invertible [] Interval Source # 
Invertible [] AbsPitch Source # 
Invertible [] Pitch Source # 

Methods

invert :: [Pitch] -> [Pitch] Source #

invertN :: Int -> [Pitch] -> [Pitch] Source #

(Show a, Invertible [] a) => Invertible Music a Source # 

Methods

invert :: Music a -> Music a Source #

invertN :: Int -> Music a -> Music a Source #

Invertible [] a => Invertible [] (Maybe a) Source # 

Methods

invert :: [Maybe a] -> [Maybe a] Source #

invertN :: Int -> [Maybe a] -> [Maybe a] Source #

Invertible [] a => Invertible [] (a, b) Source # 

Methods

invert :: [(a, b)] -> [(a, b)] Source #

invertN :: Int -> [(a, b)] -> [(a, b)] Source #

class Retrogradable f a where Source #

Minimal complete definition

(><)

Methods

(><) :: f a -> f a Source #

Instances

Retrogradable [] a Source # 

Methods

(><) :: [a] -> [a] Source #

Retrogradable Music a Source # 

Methods

(><) :: Music a -> Music a Source #

class Repeatable a where Source #

Anything that can be repeated a number of times.

Minimal complete definition

(##)

Methods

(##) :: Int -> a -> a infix 2 Source #

Instances

Repeatable (Music a) Source # 

Methods

(##) :: Int -> Music a -> Music a Source #

class Scalable a where Source #

Anything that can be scaled up/down.

Minimal complete definition

(*~)

Methods

(*~) :: Rational -> a -> a infix 3 Source #

Instances

Scalable Duration Source # 
Scalable a => Scalable [a] Source # 

Methods

(*~) :: Rational -> [a] -> [a] Source #

Scalable (Music a) Source # 

Methods

(*~) :: Rational -> Music a -> Music a Source #

musicToList :: Music a -> [(Maybe a, Duration)] Source #

Conversion to/from List.

normalize :: Music a -> Music a Source #

Normalize nested application of sequential composition.

Orphan instances

(Enum a, BoundEnum a) => Num a Source # 

Methods

(+) :: a -> a -> a #

(-) :: a -> a -> a #

(*) :: a -> a -> a #

negate :: a -> a #

abs :: a -> a #

signum :: a -> a #

fromInteger :: Integer -> a #