Safe Haskell | None |
---|
- data Handle = Handle {
- sequ :: T DuplexMode
- client :: T
- portPublic :: T
- portPrivate :: T
- queue :: T
- init :: IO Handle
- exit :: Handle -> IO ()
- with :: ReaderT Handle IO a -> IO a
- setTimeStamping :: ReaderT Handle IO ()
- startQueue :: ReaderT Handle IO ()
- connect :: String -> String -> ReaderT Handle IO ()
- connectTimidity :: ReaderT Handle IO ()
- connectLLVM :: ReaderT Handle IO ()
- connectSuperCollider :: ReaderT Handle IO ()
- sendNote :: Channel -> Time -> Velocity -> Pitch -> ReaderT Handle IO ()
- sendKey :: Channel -> Bool -> Velocity -> Pitch -> ReaderT Handle IO ()
- sendController :: Channel -> Controller -> Int -> ReaderT Handle IO ()
- sendProgram :: Channel -> Program -> ReaderT Handle IO ()
- sendMode :: Channel -> T -> ReaderT Handle IO ()
- channel :: Int -> Channel
- pitch :: Int -> Pitch
- velocity :: Int -> Velocity
- controller :: Int -> Controller
- program :: Int -> Program
- normalVelocity :: Velocity
- type TimeAbs = Rational
- newtype Time = Time {}
- consTime :: String -> Rational -> Time
- incTime :: Time -> TimeAbs -> TimeAbs
- nano :: Num a => a
- makeEvent :: Handle -> TimeAbs -> Data -> T
- makeEcho :: Handle -> TimeAbs -> Custom -> T
- outputEvent :: TimeAbs -> Data -> ReaderT Handle IO ()
- simpleNote :: Channel -> Pitch -> Velocity -> Note
- type Bundle a = [(Time, a)]
- type EventDataBundle = Bundle Data
- singletonBundle :: a -> Bundle a
- immediateBundle :: [a] -> Bundle a
- timeFromStamp :: TimeStamp -> Time
- defaultTempoCtrl :: (Channel, Controller)
- transpose :: Int -> Data -> Maybe Data
- reverse :: Data -> Maybe Data
- setChannel :: Channel -> Data -> Data
- replaceProgram :: [Int32] -> Int32 -> [Int32] -> (Bool, [Int32])
- programFromBanks :: [Int32] -> [Int32] -> Int32
- programsAsBanks :: [Int32] -> Data -> State [Int32] Data
- nextProgram :: Note -> State [Program] [Data]
- traversePrograms :: Data -> State [Program] [Data]
- traverseProgramsSeek :: Int -> Data -> State [Program] [Data]
- reduceNoteVelocity :: Word8 -> Note -> Note
- delayAdd :: Word8 -> Time -> Data -> EventDataBundle
- controllerFromNote :: (Int -> Int) -> Controller -> Data -> Maybe Data
- type KeySet = Map (Pitch, Channel) Velocity
- type KeyQueue = [((Pitch, Channel), Velocity)]
- eventsFromKey :: Time -> ((Pitch, Channel), Velocity) -> EventDataBundle
- selectFromLimittedChord :: Int -> Time -> KeyQueue -> EventDataBundle
- selectFromOctaveChord :: Int -> Time -> KeyQueue -> EventDataBundle
- selectFromChord :: Integer -> Time -> KeyQueue -> EventDataBundle
- selectFromChordRatio :: Double -> Time -> KeyQueue -> EventDataBundle
- maybePitch :: Int -> Maybe Pitch
- increasePitch :: Int -> Pitch -> Maybe Pitch
- selectInversion :: Double -> Time -> KeyQueue -> EventDataBundle
- updateChord :: NoteEv -> Note -> KeySet -> KeySet
- controllerMatch :: Channel -> Controller -> Ctrl -> Bool
- updateDur :: Ctrl -> (Time, Time) -> Time
- updateDurLinear :: Ctrl -> (Time, Time) -> Time
- updateDurExponential :: Ctrl -> (Time, Time) -> Time
- powerRationalFromFloat :: (Floating a, RealFrac a) => Int -> Int -> a -> a -> Rational
- type Selector i = i -> Time -> KeyQueue -> EventDataBundle
- data PatternMono i = PatternMono (Selector i) [i]
- data IndexNote i = IndexNote Int i
- item :: i -> Int -> IndexNote i
- data PatternPoly i = PatternPoly (Selector i) (T Int [IndexNote i])
- fraction :: RealFrac a => a -> a
- data SweepState = SweepState {}
- flipSeq :: Int -> [Int]
- bruijn :: Int -> Int -> [Int]
- bruijnAll :: Int -> Int -> [[Int]]
- bruijnAllMap :: Int -> Int -> [[Int]]
- testBruijn :: Int -> Int -> [Int] -> Bool
- testBruijnAll :: Int -> Int -> Bool
- bruijnAllTrie :: Int -> Int -> [[Int]]
- data Trie a b
- fullTrie :: b -> [a] -> Int -> Trie a b
- nullTrie :: Trie a [b] -> Bool
- deleteWord :: (Eq a, Eq b) => b -> [a] -> Trie a [b] -> Trie a [b]
- lookupWord :: Eq a => [a] -> Trie a b -> Maybe b
- bruijnAllBits :: Int -> Int -> [[Int]]
- cycleUp, crossSum, pingPong, cycleDown :: Int -> PatternMono Int
- bruijnPat :: Int -> Int -> PatternMono Int
- cycleUpAuto, crossSumAuto, pingPongAuto, cycleDownAuto :: PatternMono Integer
- binaryStaccato, binaryAccident, binaryLegato :: PatternPoly Int
- decomposePositional :: Integer -> Integer -> [Integer]
- cycleUpOctave :: Int -> PatternMono Int
- random, randomInversions :: PatternMono Double
- cycleUpInversions :: Int -> PatternMono Double
- inversions :: [Double] -> PatternMono Double
- examplePatternPolyTempo0 :: T Int [IndexNote Int]
- examplePatternPolyTempo1 :: T Int [IndexNote Int]
- checkChannel :: (Channel -> Bool) -> Data -> Bool
- checkPitch :: (Pitch -> Bool) -> Data -> Bool
- checkController :: (Controller -> Bool) -> Data -> Bool
- checkMode :: (T -> Bool) -> Data -> Bool
- checkProgram :: (Program -> Bool) -> Data -> Bool
- mergeStable :: C time => T time body -> T time body -> T time body
- mergeEither :: C time => T time a -> T time b -> T time (Either a b)
helper functions
Handle | |
|
send single events
sendController :: Channel -> Controller -> Int -> ReaderT Handle IO ()Source
constructors
controller :: Int -> ControllerSource
time
The Time
types are used instead of floating point types,
because the latter ones caused unpredictable 'negative number' errors.
The denominator must always be a power of 10,
this way we can prevent unlimited grow of denominators.
events
type Bundle a = [(Time, a)]Source
The times are relative to the start time of the bundle and do not need to be ordered.
type EventDataBundle = Bundle DataSource
singletonBundle :: a -> Bundle aSource
immediateBundle :: [a] -> Bundle aSource
timeFromStamp :: TimeStamp -> TimeSource
effects
transpose :: Int -> Data -> Maybe DataSource
Transpose a note event by the given number of semitones. Non-note events are returned without modification. If by transposition a note leaves the range of representable MIDI notes, then we return Nothing.
reverse :: Data -> Maybe DataSource
Swap order of keys. Non-note events are returned without modification. If by reversing a note leaves the range of representable MIDI notes, then we return Nothing.
setChannel :: Channel -> Data -> DataSource
replaceProgram :: [Int32] -> Int32 -> [Int32] -> (Bool, [Int32])Source
> replaceProgram [1,2,3,4] 5 [10,11,12,13] (True,[10,11,2,13])
programFromBanks :: [Int32] -> [Int32] -> Int32Source
programsAsBanks :: [Int32] -> Data -> State [Int32] DataSource
Interpret program changes as a kind of bank switches in order to increase the range of instruments that can be selected via a block of patch select buttons.
programAsBanks ns
divides the first sum ns
instruments
into sections of sizes ns!!0, ns!!1, ...
.
Each program in those sections is interpreted as a bank in a hierarchy,
where the lower program numbers are the least significant banks.
Programs from sum ns
on are passed through as they are.
product ns
is the number of instruments
that you can address using this trick.
In order to avoid overflow it should be less than 128.
E.g. programAsBanks [n,m]
interprets subsequent program changes to
a
(0<=a<n
) and n+b
(0<=b<m
)
as a program change to b*n+a
.
programAsBanks [8,8]
allows to select 64 instruments
by 16 program change buttons,
whereas programAsBanks [8,4,4]
allows to address the full range of MIDI 128 instruments
with the same number of buttons.
traversePrograms :: Data -> State [Program] [Data]Source
Before every note switch to another instrument according to a list of programs given as state of the State monad. I do not know how to handle multiple channels in a reasonable way. Currently I just switch the instrument independent from the channel, and send the program switch to the same channel as the beginning note.
traverseProgramsSeek :: Int -> Data -> State [Program] [Data]Source
This function extends traversePrograms
.
It reacts on external program changes
by seeking an according program in the list.
This way we can reset the pointer into the instrument list.
However the search must be limited in order to prevent an infinite loop
if we receive a program that is not contained in the list.
reduceNoteVelocity :: Word8 -> Note -> NoteSource
controllerFromNote :: (Int -> Int) -> Controller -> Data -> Maybe DataSource
Map NoteOn events to a controller value. This way you may play notes via the resonance frequency of a filter.
eventsFromKey :: Time -> ((Pitch, Channel), Velocity) -> EventDataBundleSource
selectFromLimittedChord :: Int -> Time -> KeyQueue -> EventDataBundleSource
selectFromOctaveChord :: Int -> Time -> KeyQueue -> EventDataBundleSource
Generate notes according to the key set, where notes for negative and too large indices are padded with keys that are transposed by octaves.
selectFromChord :: Integer -> Time -> KeyQueue -> EventDataBundleSource
selectFromChordRatio :: Double -> Time -> KeyQueue -> EventDataBundleSource
maybePitch :: Int -> Maybe PitchSource
selectInversion :: Double -> Time -> KeyQueue -> EventDataBundleSource
controllerMatch :: Channel -> Controller -> Ctrl -> BoolSource
powerRationalFromFloat :: (Floating a, RealFrac a) => Int -> Int -> a -> a -> RationalSource
Compute base ** expo
approximately to result type Rational
such that the result has a denominator which is a power of digitBase
and a relative precision of numerator of precision
digits
with respect to digitBase
-ary numbers.
type Selector i = i -> Time -> KeyQueue -> EventDataBundleSource
data PatternMono i Source
PatternMono (Selector i) [i] |
Pattern (PatternMono i) | |
Pattern (PatternMono i) |
data PatternPoly i Source
PatternPoly (Selector i) (T Int [IndexNote i]) |
Pattern (PatternPoly i) | |
Pattern (PatternPoly i) |
data SweepState Source
SweepState | |
|
patterns
See Haskore/FlipSong
flipSeq m !! n = cross sum of the m-ary representation of n modulo m.
For m=2 this yields http:www.research.att.comcgi-binaccess.cgiasnjassequenceseisA.cgi?Anum=A010060
bruijn :: Int -> Int -> [Int]Source
bruijn n k
is a sequence with length n^k
where cycle (bruijn n k)
contains all n-ary numbers with k digits as infixes.
The function computes the lexicographically smallest of such sequences.
bruijnAllMap :: Int -> Int -> [[Int]]Source
testBruijnAll :: Int -> Int -> BoolSource
bruijnAllTrie :: Int -> Int -> [[Int]]Source
lookupWord :: Eq a => [a] -> Trie a b -> Maybe bSource
bruijnAllBits :: Int -> Int -> [[Int]]Source
decomposePositional :: Integer -> Integer -> [Integer]Source
cycleUpOctave :: Int -> PatternMono IntSource
inversions :: [Double] -> PatternMono DoubleSource
predicates
checkController :: (Controller -> Bool) -> Data -> BoolSource