hs-pattrans-0.1.0.2: DSL for musical patterns and transformation, based on contravariant functors.

Safe HaskellNone
LanguageHaskell2010

Transformations

Synopsis

Documentation

newtype Check a Source #

Constructors

Check

Checks two patterns (horizontal translation in time is always assumed).

Fields

Instances

Contravariant Check Source # 

Methods

contramap :: (a -> b) -> Check b -> Check a

(>$) :: b -> Check b -> Check a

Semigroup (Check a) Source # 

Methods

(<>) :: Check a -> Check a -> Check a #

sconcat :: NonEmpty (Check a) -> Check a #

stimes :: Integral b => b -> Check a -> Check a #

(<=>) :: a -> a -> Check a -> Bool Source #

(>$<) :: (a -> b) -> Check b -> Check a infix 7 Source #

(>$) :: (a -> a) -> Check a -> Check a infix 8 Source #

($<) :: (a -> a) -> Check a -> Check a infix 8 Source #

type ApproxCheck a = (?p :: Float) => Check a Source #

(~~) :: ((?p :: Float) => r) -> Float -> r Source #

exactOf :: ApproxCheck Pattern Source #

Exact repetition: move a pattern in time. (AKA horizontal translation)

transpositionOf :: ApproxCheck Pattern Source #

Transposition: move a pattern in pitch. (AKA horizontal+vertical translation)

inversionOf :: ApproxCheck Pattern Source #

Inversion: negate all pitch intervals (starting from the same base pitch).

retrogradeOf :: ApproxCheck Pattern Source #

Retrograde: mirror a pattern in both pitch and rhythm. (AKA vertical reflection)

rotationOf :: ApproxCheck Pattern Source #

Rotation: reversal of pitch intervals and reversal of rhythm. (AKA retrograde inversion)

augmentationOf :: ApproxCheck Pattern Source #

Augmentation: speed-up/slow-down the rhythmic structure of a pattern.

tonalTranspOf :: ApproxCheck Pattern Source #

Octave-agnostic tonal transposition, wrt a scale that fits the base pattern e.g. [I, IV, V] tonalTranspOf [III, VI, VII]

tonalTranspOfCan :: ApproxCheck Pattern Source #

Taking into account of multiple possibilities of scales like in tonalTransCanofCore, but with approximation in the checking

tonalTransCanOfCore :: Check Pattern Source #

Instead guess one scale, then check the scale degrees, we guess three scales, and fold over all the possible scale degree checks with || The core is a version that does not allow for approximation

trInversionOf :: ApproxCheck Pattern Source #

Transposition + Inversion.

trAugmentationOf :: ApproxCheck Pattern Source #

Transposition + Augmentation.

trRetrogradeOf :: ApproxCheck Pattern Source #

Transposition + Retrograde.

equal :: Eq a => Check a Source #

Check that two elements are exactly equal (using eq). e.g. [a, c, b] equal [a, c, b]

maxLookahead :: Int Source #

Influences the accuracy of approxEq, but also dramatically reduces execution time of the analysis.

approxEqWith Source #

Arguments

:: (Show b, Num b, Eq b) 
=> (b -> [b] -> Int -> Maybe (Int, [b]))

function that deletes an element from a list, possibly reducing (summing) consecutive elements to be equal to the element being deleted

-> ApproxCheck [b] 

approxEq :: (Show a, Num a, Eq a) => ApproxCheck [a] Source #

First-order approximate equality of lists.

Check that two lists are approximately equal, wrt a certain percentage. A base pattern and an occurence are approximately equal with percentage p when: 1. The occurence ignores (1-p)% notes of the base pattern 2. (1-p)% notes of the occurence are additional notes (not in the base pattern) e.g. [A,C,F,A,B] (approxEq 80%) [A,C,G,A,B]

approxEq2 :: (Show a, Ord a, Num a, Eq a) => ApproxCheck [a] Source #

Second-order approximate equality of lists.

The essential difference with first-order approximate equality is the ability to equate consecutive elements with their sum, hence the Ord/Num constraint.

NB: motivated by lists which are the result of pairing an initial list and we count approximation by checking the initial lists e.g. * intervals from pitches * rhythm from durations