module Sound.Tidal.Params where -- Please note, this file is generated by bin/generate-params.hs -- Submit any pull requests against that file and/or params-header.hs -- in the same folder, thanks. {- Params.hs - Provides the basic control patterns available to TidalCycles by default Copyright (C) 2021, Alex McLean and contributors This library is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This library is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this library. If not, see . -} import qualified Data.Map.Strict as Map import Sound.Tidal.Pattern import Sound.Tidal.Core ((#)) import Sound.Tidal.Utils import Data.Maybe (fromMaybe) import Data.Word (Word8) import Data.Fixed (mod') -- | group multiple params into one grp :: [String -> ValueMap] -> Pattern String -> ControlPattern grp [] _ = empty grp fs p = splitby <$> p where splitby name = Map.unions $ map (\(v, f) -> f v) $ zip (split name) fs split :: String -> [String] split = wordsBy (==':') mF :: String -> String -> ValueMap mF name v = fromMaybe Map.empty $ do f <- readMaybe v return $ Map.singleton name (VF f) mI :: String -> String -> ValueMap mI name v = fromMaybe Map.empty $ do i <- readMaybe v return $ Map.singleton name (VI i) mS :: String -> String -> ValueMap mS name v = Map.singleton name (VS v) -- | Param makers pF :: String -> Pattern Double -> ControlPattern pF name = fmap (Map.singleton name . VF) pI :: String -> Pattern Int -> ControlPattern pI name = fmap (Map.singleton name . VI) pB :: String -> Pattern Bool -> ControlPattern pB name = fmap (Map.singleton name . VB) pR :: String -> Pattern Rational -> ControlPattern pR name = fmap (Map.singleton name . VR) pN :: String -> Pattern Note -> ControlPattern pN name = fmap (Map.singleton name . VN) pS :: String -> Pattern String -> ControlPattern pS name = fmap (Map.singleton name . VS) pX :: String -> Pattern [Word8] -> ControlPattern pX name = fmap (Map.singleton name . VX) pStateF :: String -> -- ^ A parameter, e.g. `note`; a -- `String` recognizable by a `ValueMap`. String -> -- ^ Identifies the cycling state pattern. -- Can be anything the user wants. (Maybe Double -> Double) -> ControlPattern pStateF name sName update = pure $ Map.singleton name $ VState statef where statef :: ValueMap -> (ValueMap, Value) statef sMap = (Map.insert sName v sMap, v) where v = VF $ update $ Map.lookup sName sMap >>= getF -- | `pStateList` is made with cyclic lists in mind, -- but it can even "cycle" through infinite lists. pStateList :: String -> -- ^ A parameter, e.g. `note`; a -- `String` recognizable by a `ValueMap`. String -> -- ^ Identifies the cycling state pattern. -- Can be anything the user wants. [Value] -> -- ^ The list to cycle through. ControlPattern pStateList name sName xs = pure $ Map.singleton name $ VState statef where statef :: ValueMap -> (ValueMap, Value) statef sMap = ( Map.insert sName (VList $ tail looped) sMap , head looped) where xs' = fromMaybe xs $ Map.lookup sName sMap >>= getList -- do this instead of a cycle, so it can get updated with the a list looped | null xs' = xs | otherwise = xs' -- | A wrapper for `pStateList` that accepts a `[Double]` -- rather than a `[Value]`. pStateListF :: String -> String -> [Double] -> ControlPattern pStateListF name sName = pStateList name sName . map VF -- | A wrapper for `pStateList` that accepts a `[String]` -- rather than a `[Value]`. pStateListS :: String -> String -> [String] -> ControlPattern pStateListS name sName = pStateList name sName . map VS -- | Grouped params sound :: Pattern String -> ControlPattern sound = grp [mS "s", mF "n"] sTake :: String -> [String] -> ControlPattern sTake name xs = pStateListS "s" name xs cc :: Pattern String -> ControlPattern cc = grp [mF "ccn", mF "ccv"] nrpn :: Pattern String -> ControlPattern nrpn = grp [mI "nrpn", mI "val"] nrpnn :: Pattern Int -> ControlPattern nrpnn = pI "nrpn" nrpnv :: Pattern Int -> ControlPattern nrpnv = pI "val" grain' :: Pattern String -> ControlPattern grain' = grp [mF "begin", mF "end"] midinote :: Pattern Note -> ControlPattern midinote = note . (subtract 60 <$>) drum :: Pattern String -> ControlPattern drum = n . (subtract 60 . drumN <$>) drumN :: Num a => String -> a drumN "hq" = 27 drumN "sl" = 28 drumN "ps" = 29 drumN "pl" = 30 drumN "st" = 31 drumN "sq" = 32 drumN "ml" = 33 drumN "mb" = 34 drumN "ab" = 35 drumN "bd" = 36 drumN "rm" = 37 drumN "sn" = 38 drumN "cp" = 39 drumN "es" = 40 drumN "lf" = 41 drumN "ch" = 42 drumN "lt" = 43 drumN "hh" = 44 drumN "ft" = 45 drumN "oh" = 46 drumN "mt" = 47 drumN "hm" = 48 drumN "cr" = 49 drumN "ht" = 50 drumN "ri" = 51 drumN "cy" = 52 drumN "be" = 53 drumN "ta" = 54 drumN "sc" = 55 drumN "cb" = 56 drumN "cs" = 57 drumN "vi" = 58 drumN "rc" = 59 drumN "hb" = 60 drumN "lb" = 61 drumN "mh" = 62 drumN "hc" = 63 drumN "lc" = 64 drumN "he" = 65 drumN "le" = 66 drumN "ag" = 67 drumN "la" = 68 drumN "ca" = 69 drumN "ma" = 70 drumN "sw" = 71 drumN "lw" = 72 drumN "sg" = 73 drumN "lg" = 74 drumN "cl" = 75 drumN "hi" = 76 drumN "li" = 77 drumN "mc" = 78 drumN "oc" = 79 drumN "tr" = 80 drumN "ot" = 81 drumN "sh" = 82 drumN "jb" = 83 drumN "bt" = 84 drumN "ct" = 85 drumN "ms" = 86 drumN "os" = 87 drumN _ = 0 -- Generated params -- | a pattern of numbers that speed up (or slow down) samples while they play. accelerate :: Pattern Double -> ControlPattern accelerate = pF "accelerate" accelerateTake :: String -> [Double] -> ControlPattern accelerateTake name xs = pStateListF "accelerate" name xs accelerateCount :: String -> ControlPattern accelerateCount name = pStateF "accelerate" name (maybe 0 (+1)) accelerateCountTo :: String -> Pattern Double -> Pattern ValueMap accelerateCountTo name ipat = innerJoin $ (\i -> pStateF "accelerate" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat acceleratebus :: Pattern Int -> Pattern Double -> ControlPattern acceleratebus _ _ = error $ "Control parameter 'accelerate' can't be sent to a bus." -- | like @gain@, but linear. amp :: Pattern Double -> ControlPattern amp = pF "amp" ampTake :: String -> [Double] -> ControlPattern ampTake name xs = pStateListF "amp" name xs ampCount :: String -> ControlPattern ampCount name = pStateF "amp" name (maybe 0 (+1)) ampCountTo :: String -> Pattern Double -> Pattern ValueMap ampCountTo name ipat = innerJoin $ (\i -> pStateF "amp" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat ampbus :: Pattern Int -> Pattern Double -> ControlPattern ampbus busid pat = (pF "amp" pat) # (pI "^amp" busid) amprecv :: Pattern Int -> ControlPattern amprecv busid = pI "^amp" busid -- | array :: Pattern [Word8] -> ControlPattern array = pX "array" arrayTake :: String -> [Double] -> ControlPattern arrayTake name xs = pStateListF "array" name xs arraybus :: Pattern Int -> Pattern [Word8] -> ControlPattern arraybus _ _ = error $ "Control parameter 'array' can't be sent to a bus." -- | a pattern of numbers to specify the attack time (in seconds) of an envelope applied to each sample. attack :: Pattern Double -> ControlPattern attack = pF "attack" attackTake :: String -> [Double] -> ControlPattern attackTake name xs = pStateListF "attack" name xs attackCount :: String -> ControlPattern attackCount name = pStateF "attack" name (maybe 0 (+1)) attackCountTo :: String -> Pattern Double -> Pattern ValueMap attackCountTo name ipat = innerJoin $ (\i -> pStateF "attack" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat attackbus :: Pattern Int -> Pattern Double -> ControlPattern attackbus busid pat = (pF "attack" pat) # (pI "^attack" busid) attackrecv :: Pattern Int -> ControlPattern attackrecv busid = pI "^attack" busid -- | a pattern of numbers from 0 to 1. Sets the center frequency of the band-pass filter. bandf :: Pattern Double -> ControlPattern bandf = pF "bandf" bandfTake :: String -> [Double] -> ControlPattern bandfTake name xs = pStateListF "bandf" name xs bandfCount :: String -> ControlPattern bandfCount name = pStateF "bandf" name (maybe 0 (+1)) bandfCountTo :: String -> Pattern Double -> Pattern ValueMap bandfCountTo name ipat = innerJoin $ (\i -> pStateF "bandf" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat bandfbus :: Pattern Int -> Pattern Double -> ControlPattern bandfbus busid pat = (pF "bandf" pat) # (pI "^bandf" busid) bandfrecv :: Pattern Int -> ControlPattern bandfrecv busid = pI "^bandf" busid -- | a pattern of anumbers from 0 to 1. Sets the q-factor of the band-pass filter. bandq :: Pattern Double -> ControlPattern bandq = pF "bandq" bandqTake :: String -> [Double] -> ControlPattern bandqTake name xs = pStateListF "bandq" name xs bandqCount :: String -> ControlPattern bandqCount name = pStateF "bandq" name (maybe 0 (+1)) bandqCountTo :: String -> Pattern Double -> Pattern ValueMap bandqCountTo name ipat = innerJoin $ (\i -> pStateF "bandq" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat bandqbus :: Pattern Int -> Pattern Double -> ControlPattern bandqbus busid pat = (pF "bandq" pat) # (pI "^bandq" busid) bandqrecv :: Pattern Int -> ControlPattern bandqrecv busid = pI "^bandq" busid -- | a pattern of numbers from 0 to 1. Skips the beginning of each sample, e.g. `0.25` to cut off the first quarter from each sample. begin :: Pattern Double -> ControlPattern begin = pF "begin" beginTake :: String -> [Double] -> ControlPattern beginTake name xs = pStateListF "begin" name xs beginCount :: String -> ControlPattern beginCount name = pStateF "begin" name (maybe 0 (+1)) beginCountTo :: String -> Pattern Double -> Pattern ValueMap beginCountTo name ipat = innerJoin $ (\i -> pStateF "begin" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat beginbus :: Pattern Int -> Pattern Double -> ControlPattern beginbus _ _ = error $ "Control parameter 'begin' can't be sent to a bus." -- | Spectral binshift binshift :: Pattern Double -> ControlPattern binshift = pF "binshift" binshiftTake :: String -> [Double] -> ControlPattern binshiftTake name xs = pStateListF "binshift" name xs binshiftCount :: String -> ControlPattern binshiftCount name = pStateF "binshift" name (maybe 0 (+1)) binshiftCountTo :: String -> Pattern Double -> Pattern ValueMap binshiftCountTo name ipat = innerJoin $ (\i -> pStateF "binshift" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat binshiftbus :: Pattern Int -> Pattern Double -> ControlPattern binshiftbus busid pat = (pF "binshift" pat) # (pI "^binshift" busid) binshiftrecv :: Pattern Int -> ControlPattern binshiftrecv busid = pI "^binshift" busid -- | button0 :: Pattern Double -> ControlPattern button0 = pF "button0" button0Take :: String -> [Double] -> ControlPattern button0Take name xs = pStateListF "button0" name xs button0Count :: String -> ControlPattern button0Count name = pStateF "button0" name (maybe 0 (+1)) button0CountTo :: String -> Pattern Double -> Pattern ValueMap button0CountTo name ipat = innerJoin $ (\i -> pStateF "button0" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat button0bus :: Pattern Int -> Pattern Double -> ControlPattern button0bus busid pat = (pF "button0" pat) # (pI "^button0" busid) button0recv :: Pattern Int -> ControlPattern button0recv busid = pI "^button0" busid -- | button1 :: Pattern Double -> ControlPattern button1 = pF "button1" button1Take :: String -> [Double] -> ControlPattern button1Take name xs = pStateListF "button1" name xs button1Count :: String -> ControlPattern button1Count name = pStateF "button1" name (maybe 0 (+1)) button1CountTo :: String -> Pattern Double -> Pattern ValueMap button1CountTo name ipat = innerJoin $ (\i -> pStateF "button1" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat button1bus :: Pattern Int -> Pattern Double -> ControlPattern button1bus busid pat = (pF "button1" pat) # (pI "^button1" busid) button1recv :: Pattern Int -> ControlPattern button1recv busid = pI "^button1" busid -- | button10 :: Pattern Double -> ControlPattern button10 = pF "button10" button10Take :: String -> [Double] -> ControlPattern button10Take name xs = pStateListF "button10" name xs button10Count :: String -> ControlPattern button10Count name = pStateF "button10" name (maybe 0 (+1)) button10CountTo :: String -> Pattern Double -> Pattern ValueMap button10CountTo name ipat = innerJoin $ (\i -> pStateF "button10" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat button10bus :: Pattern Int -> Pattern Double -> ControlPattern button10bus busid pat = (pF "button10" pat) # (pI "^button10" busid) button10recv :: Pattern Int -> ControlPattern button10recv busid = pI "^button10" busid -- | button11 :: Pattern Double -> ControlPattern button11 = pF "button11" button11Take :: String -> [Double] -> ControlPattern button11Take name xs = pStateListF "button11" name xs button11Count :: String -> ControlPattern button11Count name = pStateF "button11" name (maybe 0 (+1)) button11CountTo :: String -> Pattern Double -> Pattern ValueMap button11CountTo name ipat = innerJoin $ (\i -> pStateF "button11" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat button11bus :: Pattern Int -> Pattern Double -> ControlPattern button11bus busid pat = (pF "button11" pat) # (pI "^button11" busid) button11recv :: Pattern Int -> ControlPattern button11recv busid = pI "^button11" busid -- | button12 :: Pattern Double -> ControlPattern button12 = pF "button12" button12Take :: String -> [Double] -> ControlPattern button12Take name xs = pStateListF "button12" name xs button12Count :: String -> ControlPattern button12Count name = pStateF "button12" name (maybe 0 (+1)) button12CountTo :: String -> Pattern Double -> Pattern ValueMap button12CountTo name ipat = innerJoin $ (\i -> pStateF "button12" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat button12bus :: Pattern Int -> Pattern Double -> ControlPattern button12bus busid pat = (pF "button12" pat) # (pI "^button12" busid) button12recv :: Pattern Int -> ControlPattern button12recv busid = pI "^button12" busid -- | button13 :: Pattern Double -> ControlPattern button13 = pF "button13" button13Take :: String -> [Double] -> ControlPattern button13Take name xs = pStateListF "button13" name xs button13Count :: String -> ControlPattern button13Count name = pStateF "button13" name (maybe 0 (+1)) button13CountTo :: String -> Pattern Double -> Pattern ValueMap button13CountTo name ipat = innerJoin $ (\i -> pStateF "button13" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat button13bus :: Pattern Int -> Pattern Double -> ControlPattern button13bus busid pat = (pF "button13" pat) # (pI "^button13" busid) button13recv :: Pattern Int -> ControlPattern button13recv busid = pI "^button13" busid -- | button14 :: Pattern Double -> ControlPattern button14 = pF "button14" button14Take :: String -> [Double] -> ControlPattern button14Take name xs = pStateListF "button14" name xs button14Count :: String -> ControlPattern button14Count name = pStateF "button14" name (maybe 0 (+1)) button14CountTo :: String -> Pattern Double -> Pattern ValueMap button14CountTo name ipat = innerJoin $ (\i -> pStateF "button14" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat button14bus :: Pattern Int -> Pattern Double -> ControlPattern button14bus busid pat = (pF "button14" pat) # (pI "^button14" busid) button14recv :: Pattern Int -> ControlPattern button14recv busid = pI "^button14" busid -- | button15 :: Pattern Double -> ControlPattern button15 = pF "button15" button15Take :: String -> [Double] -> ControlPattern button15Take name xs = pStateListF "button15" name xs button15Count :: String -> ControlPattern button15Count name = pStateF "button15" name (maybe 0 (+1)) button15CountTo :: String -> Pattern Double -> Pattern ValueMap button15CountTo name ipat = innerJoin $ (\i -> pStateF "button15" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat button15bus :: Pattern Int -> Pattern Double -> ControlPattern button15bus busid pat = (pF "button15" pat) # (pI "^button15" busid) button15recv :: Pattern Int -> ControlPattern button15recv busid = pI "^button15" busid -- | button2 :: Pattern Double -> ControlPattern button2 = pF "button2" button2Take :: String -> [Double] -> ControlPattern button2Take name xs = pStateListF "button2" name xs button2Count :: String -> ControlPattern button2Count name = pStateF "button2" name (maybe 0 (+1)) button2CountTo :: String -> Pattern Double -> Pattern ValueMap button2CountTo name ipat = innerJoin $ (\i -> pStateF "button2" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat button2bus :: Pattern Int -> Pattern Double -> ControlPattern button2bus busid pat = (pF "button2" pat) # (pI "^button2" busid) button2recv :: Pattern Int -> ControlPattern button2recv busid = pI "^button2" busid -- | button3 :: Pattern Double -> ControlPattern button3 = pF "button3" button3Take :: String -> [Double] -> ControlPattern button3Take name xs = pStateListF "button3" name xs button3Count :: String -> ControlPattern button3Count name = pStateF "button3" name (maybe 0 (+1)) button3CountTo :: String -> Pattern Double -> Pattern ValueMap button3CountTo name ipat = innerJoin $ (\i -> pStateF "button3" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat button3bus :: Pattern Int -> Pattern Double -> ControlPattern button3bus busid pat = (pF "button3" pat) # (pI "^button3" busid) button3recv :: Pattern Int -> ControlPattern button3recv busid = pI "^button3" busid -- | button4 :: Pattern Double -> ControlPattern button4 = pF "button4" button4Take :: String -> [Double] -> ControlPattern button4Take name xs = pStateListF "button4" name xs button4Count :: String -> ControlPattern button4Count name = pStateF "button4" name (maybe 0 (+1)) button4CountTo :: String -> Pattern Double -> Pattern ValueMap button4CountTo name ipat = innerJoin $ (\i -> pStateF "button4" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat button4bus :: Pattern Int -> Pattern Double -> ControlPattern button4bus busid pat = (pF "button4" pat) # (pI "^button4" busid) button4recv :: Pattern Int -> ControlPattern button4recv busid = pI "^button4" busid -- | button5 :: Pattern Double -> ControlPattern button5 = pF "button5" button5Take :: String -> [Double] -> ControlPattern button5Take name xs = pStateListF "button5" name xs button5Count :: String -> ControlPattern button5Count name = pStateF "button5" name (maybe 0 (+1)) button5CountTo :: String -> Pattern Double -> Pattern ValueMap button5CountTo name ipat = innerJoin $ (\i -> pStateF "button5" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat button5bus :: Pattern Int -> Pattern Double -> ControlPattern button5bus busid pat = (pF "button5" pat) # (pI "^button5" busid) button5recv :: Pattern Int -> ControlPattern button5recv busid = pI "^button5" busid -- | button6 :: Pattern Double -> ControlPattern button6 = pF "button6" button6Take :: String -> [Double] -> ControlPattern button6Take name xs = pStateListF "button6" name xs button6Count :: String -> ControlPattern button6Count name = pStateF "button6" name (maybe 0 (+1)) button6CountTo :: String -> Pattern Double -> Pattern ValueMap button6CountTo name ipat = innerJoin $ (\i -> pStateF "button6" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat button6bus :: Pattern Int -> Pattern Double -> ControlPattern button6bus busid pat = (pF "button6" pat) # (pI "^button6" busid) button6recv :: Pattern Int -> ControlPattern button6recv busid = pI "^button6" busid -- | button7 :: Pattern Double -> ControlPattern button7 = pF "button7" button7Take :: String -> [Double] -> ControlPattern button7Take name xs = pStateListF "button7" name xs button7Count :: String -> ControlPattern button7Count name = pStateF "button7" name (maybe 0 (+1)) button7CountTo :: String -> Pattern Double -> Pattern ValueMap button7CountTo name ipat = innerJoin $ (\i -> pStateF "button7" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat button7bus :: Pattern Int -> Pattern Double -> ControlPattern button7bus busid pat = (pF "button7" pat) # (pI "^button7" busid) button7recv :: Pattern Int -> ControlPattern button7recv busid = pI "^button7" busid -- | button8 :: Pattern Double -> ControlPattern button8 = pF "button8" button8Take :: String -> [Double] -> ControlPattern button8Take name xs = pStateListF "button8" name xs button8Count :: String -> ControlPattern button8Count name = pStateF "button8" name (maybe 0 (+1)) button8CountTo :: String -> Pattern Double -> Pattern ValueMap button8CountTo name ipat = innerJoin $ (\i -> pStateF "button8" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat button8bus :: Pattern Int -> Pattern Double -> ControlPattern button8bus busid pat = (pF "button8" pat) # (pI "^button8" busid) button8recv :: Pattern Int -> ControlPattern button8recv busid = pI "^button8" busid -- | button9 :: Pattern Double -> ControlPattern button9 = pF "button9" button9Take :: String -> [Double] -> ControlPattern button9Take name xs = pStateListF "button9" name xs button9Count :: String -> ControlPattern button9Count name = pStateF "button9" name (maybe 0 (+1)) button9CountTo :: String -> Pattern Double -> Pattern ValueMap button9CountTo name ipat = innerJoin $ (\i -> pStateF "button9" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat button9bus :: Pattern Int -> Pattern Double -> ControlPattern button9bus busid pat = (pF "button9" pat) # (pI "^button9" busid) button9recv :: Pattern Int -> ControlPattern button9recv busid = pI "^button9" busid -- | ccn :: Pattern Double -> ControlPattern ccn = pF "ccn" ccnTake :: String -> [Double] -> ControlPattern ccnTake name xs = pStateListF "ccn" name xs ccnCount :: String -> ControlPattern ccnCount name = pStateF "ccn" name (maybe 0 (+1)) ccnCountTo :: String -> Pattern Double -> Pattern ValueMap ccnCountTo name ipat = innerJoin $ (\i -> pStateF "ccn" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat ccnbus :: Pattern Int -> Pattern Double -> ControlPattern ccnbus _ _ = error $ "Control parameter 'ccn' can't be sent to a bus." -- | ccv :: Pattern Double -> ControlPattern ccv = pF "ccv" ccvTake :: String -> [Double] -> ControlPattern ccvTake name xs = pStateListF "ccv" name xs ccvCount :: String -> ControlPattern ccvCount name = pStateF "ccv" name (maybe 0 (+1)) ccvCountTo :: String -> Pattern Double -> Pattern ValueMap ccvCountTo name ipat = innerJoin $ (\i -> pStateF "ccv" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat ccvbus :: Pattern Int -> Pattern Double -> ControlPattern ccvbus _ _ = error $ "Control parameter 'ccv' can't be sent to a bus." -- | choose the channel the pattern is sent to in superdirt channel :: Pattern Int -> ControlPattern channel = pI "channel" channelTake :: String -> [Double] -> ControlPattern channelTake name xs = pStateListF "channel" name xs channelCount :: String -> ControlPattern channelCount name = pStateF "channel" name (maybe 0 (+1)) channelCountTo :: String -> Pattern Double -> Pattern ValueMap channelCountTo name ipat = innerJoin $ (\i -> pStateF "channel" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat channelbus :: Pattern Int -> Pattern Int -> ControlPattern channelbus _ _ = error $ "Control parameter 'channel' can't be sent to a bus." -- | clhatdecay :: Pattern Double -> ControlPattern clhatdecay = pF "clhatdecay" clhatdecayTake :: String -> [Double] -> ControlPattern clhatdecayTake name xs = pStateListF "clhatdecay" name xs clhatdecayCount :: String -> ControlPattern clhatdecayCount name = pStateF "clhatdecay" name (maybe 0 (+1)) clhatdecayCountTo :: String -> Pattern Double -> Pattern ValueMap clhatdecayCountTo name ipat = innerJoin $ (\i -> pStateF "clhatdecay" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat clhatdecaybus :: Pattern Int -> Pattern Double -> ControlPattern clhatdecaybus busid pat = (pF "clhatdecay" pat) # (pI "^clhatdecay" busid) clhatdecayrecv :: Pattern Int -> ControlPattern clhatdecayrecv busid = pI "^clhatdecay" busid -- | fake-resampling, a pattern of numbers for lowering the sample rate, i.e. 1 for original 2 for half, 3 for a third and so on. coarse :: Pattern Double -> ControlPattern coarse = pF "coarse" coarseTake :: String -> [Double] -> ControlPattern coarseTake name xs = pStateListF "coarse" name xs coarseCount :: String -> ControlPattern coarseCount name = pStateF "coarse" name (maybe 0 (+1)) coarseCountTo :: String -> Pattern Double -> Pattern ValueMap coarseCountTo name ipat = innerJoin $ (\i -> pStateF "coarse" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat coarsebus :: Pattern Int -> Pattern Double -> ControlPattern coarsebus busid pat = (pF "coarse" pat) # (pI "^coarse" busid) coarserecv :: Pattern Int -> ControlPattern coarserecv busid = pI "^coarse" busid -- | Spectral comb comb :: Pattern Double -> ControlPattern comb = pF "comb" combTake :: String -> [Double] -> ControlPattern combTake name xs = pStateListF "comb" name xs combCount :: String -> ControlPattern combCount name = pStateF "comb" name (maybe 0 (+1)) combCountTo :: String -> Pattern Double -> Pattern ValueMap combCountTo name ipat = innerJoin $ (\i -> pStateF "comb" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat combbus :: Pattern Int -> Pattern Double -> ControlPattern combbus busid pat = (pF "comb" pat) # (pI "^comb" busid) combrecv :: Pattern Int -> ControlPattern combrecv busid = pI "^comb" busid -- | control :: Pattern Double -> ControlPattern control = pF "control" controlTake :: String -> [Double] -> ControlPattern controlTake name xs = pStateListF "control" name xs controlCount :: String -> ControlPattern controlCount name = pStateF "control" name (maybe 0 (+1)) controlCountTo :: String -> Pattern Double -> Pattern ValueMap controlCountTo name ipat = innerJoin $ (\i -> pStateF "control" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat controlbus :: Pattern Int -> Pattern Double -> ControlPattern controlbus _ _ = error $ "Control parameter 'control' can't be sent to a bus." -- | cps :: Pattern Double -> ControlPattern cps = pF "cps" cpsTake :: String -> [Double] -> ControlPattern cpsTake name xs = pStateListF "cps" name xs cpsCount :: String -> ControlPattern cpsCount name = pStateF "cps" name (maybe 0 (+1)) cpsCountTo :: String -> Pattern Double -> Pattern ValueMap cpsCountTo name ipat = innerJoin $ (\i -> pStateF "cps" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat cpsbus :: Pattern Int -> Pattern Double -> ControlPattern cpsbus busid pat = (pF "cps" pat) # (pI "^cps" busid) cpsrecv :: Pattern Int -> ControlPattern cpsrecv busid = pI "^cps" busid -- | bit crushing, a pattern of numbers from 1 (for drastic reduction in bit-depth) to 16 (for barely no reduction). crush :: Pattern Double -> ControlPattern crush = pF "crush" crushTake :: String -> [Double] -> ControlPattern crushTake name xs = pStateListF "crush" name xs crushCount :: String -> ControlPattern crushCount name = pStateF "crush" name (maybe 0 (+1)) crushCountTo :: String -> Pattern Double -> Pattern ValueMap crushCountTo name ipat = innerJoin $ (\i -> pStateF "crush" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat crushbus :: Pattern Int -> Pattern Double -> ControlPattern crushbus busid pat = (pF "crush" pat) # (pI "^crush" busid) crushrecv :: Pattern Int -> ControlPattern crushrecv busid = pI "^crush" busid -- | ctlNum :: Pattern Double -> ControlPattern ctlNum = pF "ctlNum" ctlNumTake :: String -> [Double] -> ControlPattern ctlNumTake name xs = pStateListF "ctlNum" name xs ctlNumCount :: String -> ControlPattern ctlNumCount name = pStateF "ctlNum" name (maybe 0 (+1)) ctlNumCountTo :: String -> Pattern Double -> Pattern ValueMap ctlNumCountTo name ipat = innerJoin $ (\i -> pStateF "ctlNum" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat ctlNumbus :: Pattern Int -> Pattern Double -> ControlPattern ctlNumbus _ _ = error $ "Control parameter 'ctlNum' can't be sent to a bus." -- | ctranspose :: Pattern Double -> ControlPattern ctranspose = pF "ctranspose" ctransposeTake :: String -> [Double] -> ControlPattern ctransposeTake name xs = pStateListF "ctranspose" name xs ctransposeCount :: String -> ControlPattern ctransposeCount name = pStateF "ctranspose" name (maybe 0 (+1)) ctransposeCountTo :: String -> Pattern Double -> Pattern ValueMap ctransposeCountTo name ipat = innerJoin $ (\i -> pStateF "ctranspose" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat ctransposebus :: Pattern Int -> Pattern Double -> ControlPattern ctransposebus busid pat = (pF "ctranspose" pat) # (pI "^ctranspose" busid) ctransposerecv :: Pattern Int -> ControlPattern ctransposerecv busid = pI "^ctranspose" busid -- | In the style of classic drum-machines, `cut` will stop a playing sample as soon as another samples with in same cutgroup is to be played. An example would be an open hi-hat followed by a closed one, essentially muting the open. cut :: Pattern Int -> ControlPattern cut = pI "cut" cutTake :: String -> [Double] -> ControlPattern cutTake name xs = pStateListF "cut" name xs cutCount :: String -> ControlPattern cutCount name = pStateF "cut" name (maybe 0 (+1)) cutCountTo :: String -> Pattern Double -> Pattern ValueMap cutCountTo name ipat = innerJoin $ (\i -> pStateF "cut" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat cutbus :: Pattern Int -> Pattern Int -> ControlPattern cutbus busid pat = (pI "cut" pat) # (pI "^cut" busid) cutrecv :: Pattern Int -> ControlPattern cutrecv busid = pI "^cut" busid -- | a pattern of numbers from 0 to 1. Applies the cutoff frequency of the low-pass filter. cutoff :: Pattern Double -> ControlPattern cutoff = pF "cutoff" cutoffTake :: String -> [Double] -> ControlPattern cutoffTake name xs = pStateListF "cutoff" name xs cutoffCount :: String -> ControlPattern cutoffCount name = pStateF "cutoff" name (maybe 0 (+1)) cutoffCountTo :: String -> Pattern Double -> Pattern ValueMap cutoffCountTo name ipat = innerJoin $ (\i -> pStateF "cutoff" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat cutoffbus :: Pattern Int -> Pattern Double -> ControlPattern cutoffbus busid pat = (pF "cutoff" pat) # (pI "^cutoff" busid) cutoffrecv :: Pattern Int -> ControlPattern cutoffrecv busid = pI "^cutoff" busid -- | cutoffegint :: Pattern Double -> ControlPattern cutoffegint = pF "cutoffegint" cutoffegintTake :: String -> [Double] -> ControlPattern cutoffegintTake name xs = pStateListF "cutoffegint" name xs cutoffegintCount :: String -> ControlPattern cutoffegintCount name = pStateF "cutoffegint" name (maybe 0 (+1)) cutoffegintCountTo :: String -> Pattern Double -> Pattern ValueMap cutoffegintCountTo name ipat = innerJoin $ (\i -> pStateF "cutoffegint" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat cutoffegintbus :: Pattern Int -> Pattern Double -> ControlPattern cutoffegintbus busid pat = (pF "cutoffegint" pat) # (pI "^cutoffegint" busid) cutoffegintrecv :: Pattern Int -> ControlPattern cutoffegintrecv busid = pI "^cutoffegint" busid -- | decay :: Pattern Double -> ControlPattern decay = pF "decay" decayTake :: String -> [Double] -> ControlPattern decayTake name xs = pStateListF "decay" name xs decayCount :: String -> ControlPattern decayCount name = pStateF "decay" name (maybe 0 (+1)) decayCountTo :: String -> Pattern Double -> Pattern ValueMap decayCountTo name ipat = innerJoin $ (\i -> pStateF "decay" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat decaybus :: Pattern Int -> Pattern Double -> ControlPattern decaybus busid pat = (pF "decay" pat) # (pI "^decay" busid) decayrecv :: Pattern Int -> ControlPattern decayrecv busid = pI "^decay" busid -- | degree :: Pattern Double -> ControlPattern degree = pF "degree" degreeTake :: String -> [Double] -> ControlPattern degreeTake name xs = pStateListF "degree" name xs degreeCount :: String -> ControlPattern degreeCount name = pStateF "degree" name (maybe 0 (+1)) degreeCountTo :: String -> Pattern Double -> Pattern ValueMap degreeCountTo name ipat = innerJoin $ (\i -> pStateF "degree" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat degreebus :: Pattern Int -> Pattern Double -> ControlPattern degreebus busid pat = (pF "degree" pat) # (pI "^degree" busid) degreerecv :: Pattern Int -> ControlPattern degreerecv busid = pI "^degree" busid -- | a pattern of numbers from 0 to 1. Sets the level of the delay signal. delay :: Pattern Double -> ControlPattern delay = pF "delay" delayTake :: String -> [Double] -> ControlPattern delayTake name xs = pStateListF "delay" name xs delayCount :: String -> ControlPattern delayCount name = pStateF "delay" name (maybe 0 (+1)) delayCountTo :: String -> Pattern Double -> Pattern ValueMap delayCountTo name ipat = innerJoin $ (\i -> pStateF "delay" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat delaybus :: Pattern Int -> Pattern Double -> ControlPattern delaybus busid pat = (pF "delay" pat) # (pI "^delay" busid) delayrecv :: Pattern Int -> ControlPattern delayrecv busid = pI "^delay" busid -- | a pattern of numbers from 0 to 1. Sets the amount of delay feedback. delayfeedback :: Pattern Double -> ControlPattern delayfeedback = pF "delayfeedback" delayfeedbackTake :: String -> [Double] -> ControlPattern delayfeedbackTake name xs = pStateListF "delayfeedback" name xs delayfeedbackCount :: String -> ControlPattern delayfeedbackCount name = pStateF "delayfeedback" name (maybe 0 (+1)) delayfeedbackCountTo :: String -> Pattern Double -> Pattern ValueMap delayfeedbackCountTo name ipat = innerJoin $ (\i -> pStateF "delayfeedback" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat delayfeedbackbus :: Pattern Int -> Pattern Double -> ControlPattern delayfeedbackbus busid pat = (pF "delayfeedback" pat) # (pI "^delayfeedback" busid) delayfeedbackrecv :: Pattern Int -> ControlPattern delayfeedbackrecv busid = pI "^delayfeedback" busid -- | a pattern of numbers from 0 to 1. Sets the length of the delay. delaytime :: Pattern Double -> ControlPattern delaytime = pF "delaytime" delaytimeTake :: String -> [Double] -> ControlPattern delaytimeTake name xs = pStateListF "delaytime" name xs delaytimeCount :: String -> ControlPattern delaytimeCount name = pStateF "delaytime" name (maybe 0 (+1)) delaytimeCountTo :: String -> Pattern Double -> Pattern ValueMap delaytimeCountTo name ipat = innerJoin $ (\i -> pStateF "delaytime" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat delaytimebus :: Pattern Int -> Pattern Double -> ControlPattern delaytimebus busid pat = (pF "delaytime" pat) # (pI "^delaytime" busid) delaytimerecv :: Pattern Int -> ControlPattern delaytimerecv busid = pI "^delaytime" busid -- | detune :: Pattern Double -> ControlPattern detune = pF "detune" detuneTake :: String -> [Double] -> ControlPattern detuneTake name xs = pStateListF "detune" name xs detuneCount :: String -> ControlPattern detuneCount name = pStateF "detune" name (maybe 0 (+1)) detuneCountTo :: String -> Pattern Double -> Pattern ValueMap detuneCountTo name ipat = innerJoin $ (\i -> pStateF "detune" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat detunebus :: Pattern Int -> Pattern Double -> ControlPattern detunebus busid pat = (pF "detune" pat) # (pI "^detune" busid) detunerecv :: Pattern Int -> ControlPattern detunerecv busid = pI "^detune" busid -- | noisy fuzzy distortion distort :: Pattern Double -> ControlPattern distort = pF "distort" distortTake :: String -> [Double] -> ControlPattern distortTake name xs = pStateListF "distort" name xs distortCount :: String -> ControlPattern distortCount name = pStateF "distort" name (maybe 0 (+1)) distortCountTo :: String -> Pattern Double -> Pattern ValueMap distortCountTo name ipat = innerJoin $ (\i -> pStateF "distort" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat distortbus :: Pattern Int -> Pattern Double -> ControlPattern distortbus busid pat = (pF "distort" pat) # (pI "^distort" busid) distortrecv :: Pattern Int -> ControlPattern distortrecv busid = pI "^distort" busid -- | DJ filter, below 0.5 is low pass filter, above is high pass filter. djf :: Pattern Double -> ControlPattern djf = pF "djf" djfTake :: String -> [Double] -> ControlPattern djfTake name xs = pStateListF "djf" name xs djfCount :: String -> ControlPattern djfCount name = pStateF "djf" name (maybe 0 (+1)) djfCountTo :: String -> Pattern Double -> Pattern ValueMap djfCountTo name ipat = innerJoin $ (\i -> pStateF "djf" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat djfbus :: Pattern Int -> Pattern Double -> ControlPattern djfbus busid pat = (pF "djf" pat) # (pI "^djf" busid) djfrecv :: Pattern Int -> ControlPattern djfrecv busid = pI "^djf" busid -- | when set to `1` will disable all reverb for this pattern. See `room` and `size` for more information about reverb. dry :: Pattern Double -> ControlPattern dry = pF "dry" dryTake :: String -> [Double] -> ControlPattern dryTake name xs = pStateListF "dry" name xs dryCount :: String -> ControlPattern dryCount name = pStateF "dry" name (maybe 0 (+1)) dryCountTo :: String -> Pattern Double -> Pattern ValueMap dryCountTo name ipat = innerJoin $ (\i -> pStateF "dry" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat drybus :: Pattern Int -> Pattern Double -> ControlPattern drybus busid pat = (pF "dry" pat) # (pI "^dry" busid) dryrecv :: Pattern Int -> ControlPattern dryrecv busid = pI "^dry" busid -- | dur :: Pattern Double -> ControlPattern dur = pF "dur" durTake :: String -> [Double] -> ControlPattern durTake name xs = pStateListF "dur" name xs durCount :: String -> ControlPattern durCount name = pStateF "dur" name (maybe 0 (+1)) durCountTo :: String -> Pattern Double -> Pattern ValueMap durCountTo name ipat = innerJoin $ (\i -> pStateF "dur" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat durbus :: Pattern Int -> Pattern Double -> ControlPattern durbus busid pat = (pF "dur" pat) # (pI "^dur" busid) durrecv :: Pattern Int -> ControlPattern durrecv busid = pI "^dur" busid -- | the same as `begin`, but cuts the end off samples, shortening them; e.g. `0.75` to cut off the last quarter of each sample. end :: Pattern Double -> ControlPattern end = pF "end" endTake :: String -> [Double] -> ControlPattern endTake name xs = pStateListF "end" name xs endCount :: String -> ControlPattern endCount name = pStateF "end" name (maybe 0 (+1)) endCountTo :: String -> Pattern Double -> Pattern ValueMap endCountTo name ipat = innerJoin $ (\i -> pStateF "end" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat endbus :: Pattern Int -> Pattern Double -> ControlPattern endbus _ _ = error $ "Control parameter 'end' can't be sent to a bus." -- | Spectral enhance enhance :: Pattern Double -> ControlPattern enhance = pF "enhance" enhanceTake :: String -> [Double] -> ControlPattern enhanceTake name xs = pStateListF "enhance" name xs enhanceCount :: String -> ControlPattern enhanceCount name = pStateF "enhance" name (maybe 0 (+1)) enhanceCountTo :: String -> Pattern Double -> Pattern ValueMap enhanceCountTo name ipat = innerJoin $ (\i -> pStateF "enhance" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat enhancebus :: Pattern Int -> Pattern Double -> ControlPattern enhancebus busid pat = (pF "enhance" pat) # (pI "^enhance" busid) enhancerecv :: Pattern Int -> ControlPattern enhancerecv busid = pI "^enhance" busid -- | expression :: Pattern Double -> ControlPattern expression = pF "expression" expressionTake :: String -> [Double] -> ControlPattern expressionTake name xs = pStateListF "expression" name xs expressionCount :: String -> ControlPattern expressionCount name = pStateF "expression" name (maybe 0 (+1)) expressionCountTo :: String -> Pattern Double -> Pattern ValueMap expressionCountTo name ipat = innerJoin $ (\i -> pStateF "expression" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat expressionbus :: Pattern Int -> Pattern Double -> ControlPattern expressionbus busid pat = (pF "expression" pat) # (pI "^expression" busid) expressionrecv :: Pattern Int -> ControlPattern expressionrecv busid = pI "^expression" busid -- | As with fadeTime, but controls the fade in time of the grain envelope. Not used if the grain begins at position 0 in the sample. fadeInTime :: Pattern Double -> ControlPattern fadeInTime = pF "fadeInTime" fadeInTimeTake :: String -> [Double] -> ControlPattern fadeInTimeTake name xs = pStateListF "fadeInTime" name xs fadeInTimeCount :: String -> ControlPattern fadeInTimeCount name = pStateF "fadeInTime" name (maybe 0 (+1)) fadeInTimeCountTo :: String -> Pattern Double -> Pattern ValueMap fadeInTimeCountTo name ipat = innerJoin $ (\i -> pStateF "fadeInTime" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat fadeInTimebus :: Pattern Int -> Pattern Double -> ControlPattern fadeInTimebus _ _ = error $ "Control parameter 'fadeInTime' can't be sent to a bus." -- | Used when using begin/end or chop/striate and friends, to change the fade out time of the 'grain' envelope. fadeTime :: Pattern Double -> ControlPattern fadeTime = pF "fadeTime" fadeTimeTake :: String -> [Double] -> ControlPattern fadeTimeTake name xs = pStateListF "fadeTime" name xs fadeTimeCount :: String -> ControlPattern fadeTimeCount name = pStateF "fadeTime" name (maybe 0 (+1)) fadeTimeCountTo :: String -> Pattern Double -> Pattern ValueMap fadeTimeCountTo name ipat = innerJoin $ (\i -> pStateF "fadeTime" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat fadeTimebus :: Pattern Int -> Pattern Double -> ControlPattern fadeTimebus _ _ = error $ "Control parameter 'fadeTime' can't be sent to a bus." -- | frameRate :: Pattern Double -> ControlPattern frameRate = pF "frameRate" frameRateTake :: String -> [Double] -> ControlPattern frameRateTake name xs = pStateListF "frameRate" name xs frameRateCount :: String -> ControlPattern frameRateCount name = pStateF "frameRate" name (maybe 0 (+1)) frameRateCountTo :: String -> Pattern Double -> Pattern ValueMap frameRateCountTo name ipat = innerJoin $ (\i -> pStateF "frameRate" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat frameRatebus :: Pattern Int -> Pattern Double -> ControlPattern frameRatebus _ _ = error $ "Control parameter 'frameRate' can't be sent to a bus." -- | frames :: Pattern Double -> ControlPattern frames = pF "frames" framesTake :: String -> [Double] -> ControlPattern framesTake name xs = pStateListF "frames" name xs framesCount :: String -> ControlPattern framesCount name = pStateF "frames" name (maybe 0 (+1)) framesCountTo :: String -> Pattern Double -> Pattern ValueMap framesCountTo name ipat = innerJoin $ (\i -> pStateF "frames" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat framesbus :: Pattern Int -> Pattern Double -> ControlPattern framesbus _ _ = error $ "Control parameter 'frames' can't be sent to a bus." -- | Spectral freeze freeze :: Pattern Double -> ControlPattern freeze = pF "freeze" freezeTake :: String -> [Double] -> ControlPattern freezeTake name xs = pStateListF "freeze" name xs freezeCount :: String -> ControlPattern freezeCount name = pStateF "freeze" name (maybe 0 (+1)) freezeCountTo :: String -> Pattern Double -> Pattern ValueMap freezeCountTo name ipat = innerJoin $ (\i -> pStateF "freeze" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat freezebus :: Pattern Int -> Pattern Double -> ControlPattern freezebus busid pat = (pF "freeze" pat) # (pI "^freeze" busid) freezerecv :: Pattern Int -> ControlPattern freezerecv busid = pI "^freeze" busid -- | freq :: Pattern Double -> ControlPattern freq = pF "freq" freqTake :: String -> [Double] -> ControlPattern freqTake name xs = pStateListF "freq" name xs freqCount :: String -> ControlPattern freqCount name = pStateF "freq" name (maybe 0 (+1)) freqCountTo :: String -> Pattern Double -> Pattern ValueMap freqCountTo name ipat = innerJoin $ (\i -> pStateF "freq" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat freqbus :: Pattern Int -> Pattern Double -> ControlPattern freqbus busid pat = (pF "freq" pat) # (pI "^freq" busid) freqrecv :: Pattern Int -> ControlPattern freqrecv busid = pI "^freq" busid -- | for internal sound routing from :: Pattern Double -> ControlPattern from = pF "from" fromTake :: String -> [Double] -> ControlPattern fromTake name xs = pStateListF "from" name xs fromCount :: String -> ControlPattern fromCount name = pStateF "from" name (maybe 0 (+1)) fromCountTo :: String -> Pattern Double -> Pattern ValueMap fromCountTo name ipat = innerJoin $ (\i -> pStateF "from" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat frombus :: Pattern Int -> Pattern Double -> ControlPattern frombus busid pat = (pF "from" pat) # (pI "^from" busid) fromrecv :: Pattern Int -> ControlPattern fromrecv busid = pI "^from" busid -- | frequency shifter fshift :: Pattern Double -> ControlPattern fshift = pF "fshift" fshiftTake :: String -> [Double] -> ControlPattern fshiftTake name xs = pStateListF "fshift" name xs fshiftCount :: String -> ControlPattern fshiftCount name = pStateF "fshift" name (maybe 0 (+1)) fshiftCountTo :: String -> Pattern Double -> Pattern ValueMap fshiftCountTo name ipat = innerJoin $ (\i -> pStateF "fshift" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat fshiftbus :: Pattern Int -> Pattern Double -> ControlPattern fshiftbus busid pat = (pF "fshift" pat) # (pI "^fshift" busid) fshiftrecv :: Pattern Int -> ControlPattern fshiftrecv busid = pI "^fshift" busid -- | frequency shifter fshiftnote :: Pattern Double -> ControlPattern fshiftnote = pF "fshiftnote" fshiftnoteTake :: String -> [Double] -> ControlPattern fshiftnoteTake name xs = pStateListF "fshiftnote" name xs fshiftnoteCount :: String -> ControlPattern fshiftnoteCount name = pStateF "fshiftnote" name (maybe 0 (+1)) fshiftnoteCountTo :: String -> Pattern Double -> Pattern ValueMap fshiftnoteCountTo name ipat = innerJoin $ (\i -> pStateF "fshiftnote" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat fshiftnotebus :: Pattern Int -> Pattern Double -> ControlPattern fshiftnotebus busid pat = (pF "fshiftnote" pat) # (pI "^fshiftnote" busid) fshiftnoterecv :: Pattern Int -> ControlPattern fshiftnoterecv busid = pI "^fshiftnote" busid -- | frequency shifter fshiftphase :: Pattern Double -> ControlPattern fshiftphase = pF "fshiftphase" fshiftphaseTake :: String -> [Double] -> ControlPattern fshiftphaseTake name xs = pStateListF "fshiftphase" name xs fshiftphaseCount :: String -> ControlPattern fshiftphaseCount name = pStateF "fshiftphase" name (maybe 0 (+1)) fshiftphaseCountTo :: String -> Pattern Double -> Pattern ValueMap fshiftphaseCountTo name ipat = innerJoin $ (\i -> pStateF "fshiftphase" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat fshiftphasebus :: Pattern Int -> Pattern Double -> ControlPattern fshiftphasebus busid pat = (pF "fshiftphase" pat) # (pI "^fshiftphase" busid) fshiftphaserecv :: Pattern Int -> ControlPattern fshiftphaserecv busid = pI "^fshiftphase" busid -- | a pattern of numbers that specify volume. Values less than 1 make the sound quieter. Values greater than 1 make the sound louder. For the linear equivalent, see @amp@. gain :: Pattern Double -> ControlPattern gain = pF "gain" gainTake :: String -> [Double] -> ControlPattern gainTake name xs = pStateListF "gain" name xs gainCount :: String -> ControlPattern gainCount name = pStateF "gain" name (maybe 0 (+1)) gainCountTo :: String -> Pattern Double -> Pattern ValueMap gainCountTo name ipat = innerJoin $ (\i -> pStateF "gain" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat gainbus :: Pattern Int -> Pattern Double -> ControlPattern gainbus _ _ = error $ "Control parameter 'gain' can't be sent to a bus." -- | gate :: Pattern Double -> ControlPattern gate = pF "gate" gateTake :: String -> [Double] -> ControlPattern gateTake name xs = pStateListF "gate" name xs gateCount :: String -> ControlPattern gateCount name = pStateF "gate" name (maybe 0 (+1)) gateCountTo :: String -> Pattern Double -> Pattern ValueMap gateCountTo name ipat = innerJoin $ (\i -> pStateF "gate" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat gatebus :: Pattern Int -> Pattern Double -> ControlPattern gatebus busid pat = (pF "gate" pat) # (pI "^gate" busid) gaterecv :: Pattern Int -> ControlPattern gaterecv busid = pI "^gate" busid -- | harmonic :: Pattern Double -> ControlPattern harmonic = pF "harmonic" harmonicTake :: String -> [Double] -> ControlPattern harmonicTake name xs = pStateListF "harmonic" name xs harmonicCount :: String -> ControlPattern harmonicCount name = pStateF "harmonic" name (maybe 0 (+1)) harmonicCountTo :: String -> Pattern Double -> Pattern ValueMap harmonicCountTo name ipat = innerJoin $ (\i -> pStateF "harmonic" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat harmonicbus :: Pattern Int -> Pattern Double -> ControlPattern harmonicbus busid pat = (pF "harmonic" pat) # (pI "^harmonic" busid) harmonicrecv :: Pattern Int -> ControlPattern harmonicrecv busid = pI "^harmonic" busid -- | hatgrain :: Pattern Double -> ControlPattern hatgrain = pF "hatgrain" hatgrainTake :: String -> [Double] -> ControlPattern hatgrainTake name xs = pStateListF "hatgrain" name xs hatgrainCount :: String -> ControlPattern hatgrainCount name = pStateF "hatgrain" name (maybe 0 (+1)) hatgrainCountTo :: String -> Pattern Double -> Pattern ValueMap hatgrainCountTo name ipat = innerJoin $ (\i -> pStateF "hatgrain" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat hatgrainbus :: Pattern Int -> Pattern Double -> ControlPattern hatgrainbus busid pat = (pF "hatgrain" pat) # (pI "^hatgrain" busid) hatgrainrecv :: Pattern Int -> ControlPattern hatgrainrecv busid = pI "^hatgrain" busid -- | High pass sort of spectral filter hbrick :: Pattern Double -> ControlPattern hbrick = pF "hbrick" hbrickTake :: String -> [Double] -> ControlPattern hbrickTake name xs = pStateListF "hbrick" name xs hbrickCount :: String -> ControlPattern hbrickCount name = pStateF "hbrick" name (maybe 0 (+1)) hbrickCountTo :: String -> Pattern Double -> Pattern ValueMap hbrickCountTo name ipat = innerJoin $ (\i -> pStateF "hbrick" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat hbrickbus :: Pattern Int -> Pattern Double -> ControlPattern hbrickbus busid pat = (pF "hbrick" pat) # (pI "^hbrick" busid) hbrickrecv :: Pattern Int -> ControlPattern hbrickrecv busid = pI "^hbrick" busid -- | a pattern of numbers from 0 to 1. Applies the cutoff frequency of the high-pass filter. Also has alias @hpf@ hcutoff :: Pattern Double -> ControlPattern hcutoff = pF "hcutoff" hcutoffTake :: String -> [Double] -> ControlPattern hcutoffTake name xs = pStateListF "hcutoff" name xs hcutoffCount :: String -> ControlPattern hcutoffCount name = pStateF "hcutoff" name (maybe 0 (+1)) hcutoffCountTo :: String -> Pattern Double -> Pattern ValueMap hcutoffCountTo name ipat = innerJoin $ (\i -> pStateF "hcutoff" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat hcutoffbus :: Pattern Int -> Pattern Double -> ControlPattern hcutoffbus busid pat = (pF "hcutoff" pat) # (pI "^hcutoff" busid) hcutoffrecv :: Pattern Int -> ControlPattern hcutoffrecv busid = pI "^hcutoff" busid -- | a pattern of numbers to specify the hold time (in seconds) of an envelope applied to each sample. Only takes effect if `attack` and `release` are also specified. hold :: Pattern Double -> ControlPattern hold = pF "hold" holdTake :: String -> [Double] -> ControlPattern holdTake name xs = pStateListF "hold" name xs holdCount :: String -> ControlPattern holdCount name = pStateF "hold" name (maybe 0 (+1)) holdCountTo :: String -> Pattern Double -> Pattern ValueMap holdCountTo name ipat = innerJoin $ (\i -> pStateF "hold" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat holdbus :: Pattern Int -> Pattern Double -> ControlPattern holdbus busid pat = (pF "hold" pat) # (pI "^hold" busid) holdrecv :: Pattern Int -> ControlPattern holdrecv busid = pI "^hold" busid -- | hours :: Pattern Double -> ControlPattern hours = pF "hours" hoursTake :: String -> [Double] -> ControlPattern hoursTake name xs = pStateListF "hours" name xs hoursCount :: String -> ControlPattern hoursCount name = pStateF "hours" name (maybe 0 (+1)) hoursCountTo :: String -> Pattern Double -> Pattern ValueMap hoursCountTo name ipat = innerJoin $ (\i -> pStateF "hours" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat hoursbus :: Pattern Int -> Pattern Double -> ControlPattern hoursbus _ _ = error $ "Control parameter 'hours' can't be sent to a bus." -- | a pattern of numbers from 0 to 1. Applies the resonance of the high-pass filter. Has alias @hpq@ hresonance :: Pattern Double -> ControlPattern hresonance = pF "hresonance" hresonanceTake :: String -> [Double] -> ControlPattern hresonanceTake name xs = pStateListF "hresonance" name xs hresonanceCount :: String -> ControlPattern hresonanceCount name = pStateF "hresonance" name (maybe 0 (+1)) hresonanceCountTo :: String -> Pattern Double -> Pattern ValueMap hresonanceCountTo name ipat = innerJoin $ (\i -> pStateF "hresonance" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat hresonancebus :: Pattern Int -> Pattern Double -> ControlPattern hresonancebus busid pat = (pF "hresonance" pat) # (pI "^hresonance" busid) hresonancerecv :: Pattern Int -> ControlPattern hresonancerecv busid = pI "^hresonance" busid -- | imag :: Pattern Double -> ControlPattern imag = pF "imag" imagTake :: String -> [Double] -> ControlPattern imagTake name xs = pStateListF "imag" name xs imagCount :: String -> ControlPattern imagCount name = pStateF "imag" name (maybe 0 (+1)) imagCountTo :: String -> Pattern Double -> Pattern ValueMap imagCountTo name ipat = innerJoin $ (\i -> pStateF "imag" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat imagbus :: Pattern Int -> Pattern Double -> ControlPattern imagbus busid pat = (pF "imag" pat) # (pI "^imag" busid) imagrecv :: Pattern Int -> ControlPattern imagrecv busid = pI "^imag" busid -- | kcutoff :: Pattern Double -> ControlPattern kcutoff = pF "kcutoff" kcutoffTake :: String -> [Double] -> ControlPattern kcutoffTake name xs = pStateListF "kcutoff" name xs kcutoffCount :: String -> ControlPattern kcutoffCount name = pStateF "kcutoff" name (maybe 0 (+1)) kcutoffCountTo :: String -> Pattern Double -> Pattern ValueMap kcutoffCountTo name ipat = innerJoin $ (\i -> pStateF "kcutoff" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat kcutoffbus :: Pattern Int -> Pattern Double -> ControlPattern kcutoffbus busid pat = (pF "kcutoff" pat) # (pI "^kcutoff" busid) kcutoffrecv :: Pattern Int -> ControlPattern kcutoffrecv busid = pI "^kcutoff" busid -- | shape/bass enhancer krush :: Pattern Double -> ControlPattern krush = pF "krush" krushTake :: String -> [Double] -> ControlPattern krushTake name xs = pStateListF "krush" name xs krushCount :: String -> ControlPattern krushCount name = pStateF "krush" name (maybe 0 (+1)) krushCountTo :: String -> Pattern Double -> Pattern ValueMap krushCountTo name ipat = innerJoin $ (\i -> pStateF "krush" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat krushbus :: Pattern Int -> Pattern Double -> ControlPattern krushbus busid pat = (pF "krush" pat) # (pI "^krush" busid) krushrecv :: Pattern Int -> ControlPattern krushrecv busid = pI "^krush" busid -- | lagogo :: Pattern Double -> ControlPattern lagogo = pF "lagogo" lagogoTake :: String -> [Double] -> ControlPattern lagogoTake name xs = pStateListF "lagogo" name xs lagogoCount :: String -> ControlPattern lagogoCount name = pStateF "lagogo" name (maybe 0 (+1)) lagogoCountTo :: String -> Pattern Double -> Pattern ValueMap lagogoCountTo name ipat = innerJoin $ (\i -> pStateF "lagogo" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat lagogobus :: Pattern Int -> Pattern Double -> ControlPattern lagogobus busid pat = (pF "lagogo" pat) # (pI "^lagogo" busid) lagogorecv :: Pattern Int -> ControlPattern lagogorecv busid = pI "^lagogo" busid -- | Low pass sort of spectral filter lbrick :: Pattern Double -> ControlPattern lbrick = pF "lbrick" lbrickTake :: String -> [Double] -> ControlPattern lbrickTake name xs = pStateListF "lbrick" name xs lbrickCount :: String -> ControlPattern lbrickCount name = pStateF "lbrick" name (maybe 0 (+1)) lbrickCountTo :: String -> Pattern Double -> Pattern ValueMap lbrickCountTo name ipat = innerJoin $ (\i -> pStateF "lbrick" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat lbrickbus :: Pattern Int -> Pattern Double -> ControlPattern lbrickbus busid pat = (pF "lbrick" pat) # (pI "^lbrick" busid) lbrickrecv :: Pattern Int -> ControlPattern lbrickrecv busid = pI "^lbrick" busid -- | lclap :: Pattern Double -> ControlPattern lclap = pF "lclap" lclapTake :: String -> [Double] -> ControlPattern lclapTake name xs = pStateListF "lclap" name xs lclapCount :: String -> ControlPattern lclapCount name = pStateF "lclap" name (maybe 0 (+1)) lclapCountTo :: String -> Pattern Double -> Pattern ValueMap lclapCountTo name ipat = innerJoin $ (\i -> pStateF "lclap" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat lclapbus :: Pattern Int -> Pattern Double -> ControlPattern lclapbus busid pat = (pF "lclap" pat) # (pI "^lclap" busid) lclaprecv :: Pattern Int -> ControlPattern lclaprecv busid = pI "^lclap" busid -- | lclaves :: Pattern Double -> ControlPattern lclaves = pF "lclaves" lclavesTake :: String -> [Double] -> ControlPattern lclavesTake name xs = pStateListF "lclaves" name xs lclavesCount :: String -> ControlPattern lclavesCount name = pStateF "lclaves" name (maybe 0 (+1)) lclavesCountTo :: String -> Pattern Double -> Pattern ValueMap lclavesCountTo name ipat = innerJoin $ (\i -> pStateF "lclaves" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat lclavesbus :: Pattern Int -> Pattern Double -> ControlPattern lclavesbus busid pat = (pF "lclaves" pat) # (pI "^lclaves" busid) lclavesrecv :: Pattern Int -> ControlPattern lclavesrecv busid = pI "^lclaves" busid -- | lclhat :: Pattern Double -> ControlPattern lclhat = pF "lclhat" lclhatTake :: String -> [Double] -> ControlPattern lclhatTake name xs = pStateListF "lclhat" name xs lclhatCount :: String -> ControlPattern lclhatCount name = pStateF "lclhat" name (maybe 0 (+1)) lclhatCountTo :: String -> Pattern Double -> Pattern ValueMap lclhatCountTo name ipat = innerJoin $ (\i -> pStateF "lclhat" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat lclhatbus :: Pattern Int -> Pattern Double -> ControlPattern lclhatbus busid pat = (pF "lclhat" pat) # (pI "^lclhat" busid) lclhatrecv :: Pattern Int -> ControlPattern lclhatrecv busid = pI "^lclhat" busid -- | lcrash :: Pattern Double -> ControlPattern lcrash = pF "lcrash" lcrashTake :: String -> [Double] -> ControlPattern lcrashTake name xs = pStateListF "lcrash" name xs lcrashCount :: String -> ControlPattern lcrashCount name = pStateF "lcrash" name (maybe 0 (+1)) lcrashCountTo :: String -> Pattern Double -> Pattern ValueMap lcrashCountTo name ipat = innerJoin $ (\i -> pStateF "lcrash" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat lcrashbus :: Pattern Int -> Pattern Double -> ControlPattern lcrashbus busid pat = (pF "lcrash" pat) # (pI "^lcrash" busid) lcrashrecv :: Pattern Int -> ControlPattern lcrashrecv busid = pI "^lcrash" busid -- | controls the amount of overlap between two adjacent sounds legato :: Pattern Double -> ControlPattern legato = pF "legato" legatoTake :: String -> [Double] -> ControlPattern legatoTake name xs = pStateListF "legato" name xs legatoCount :: String -> ControlPattern legatoCount name = pStateF "legato" name (maybe 0 (+1)) legatoCountTo :: String -> Pattern Double -> Pattern ValueMap legatoCountTo name ipat = innerJoin $ (\i -> pStateF "legato" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat legatobus :: Pattern Int -> Pattern Double -> ControlPattern legatobus _ _ = error $ "Control parameter 'legato' can't be sent to a bus." -- | leslie :: Pattern Double -> ControlPattern leslie = pF "leslie" leslieTake :: String -> [Double] -> ControlPattern leslieTake name xs = pStateListF "leslie" name xs leslieCount :: String -> ControlPattern leslieCount name = pStateF "leslie" name (maybe 0 (+1)) leslieCountTo :: String -> Pattern Double -> Pattern ValueMap leslieCountTo name ipat = innerJoin $ (\i -> pStateF "leslie" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat lesliebus :: Pattern Int -> Pattern Double -> ControlPattern lesliebus busid pat = (pF "leslie" pat) # (pI "^leslie" busid) leslierecv :: Pattern Int -> ControlPattern leslierecv busid = pI "^leslie" busid -- | lfo :: Pattern Double -> ControlPattern lfo = pF "lfo" lfoTake :: String -> [Double] -> ControlPattern lfoTake name xs = pStateListF "lfo" name xs lfoCount :: String -> ControlPattern lfoCount name = pStateF "lfo" name (maybe 0 (+1)) lfoCountTo :: String -> Pattern Double -> Pattern ValueMap lfoCountTo name ipat = innerJoin $ (\i -> pStateF "lfo" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat lfobus :: Pattern Int -> Pattern Double -> ControlPattern lfobus busid pat = (pF "lfo" pat) # (pI "^lfo" busid) lforecv :: Pattern Int -> ControlPattern lforecv busid = pI "^lfo" busid -- | lfocutoffint :: Pattern Double -> ControlPattern lfocutoffint = pF "lfocutoffint" lfocutoffintTake :: String -> [Double] -> ControlPattern lfocutoffintTake name xs = pStateListF "lfocutoffint" name xs lfocutoffintCount :: String -> ControlPattern lfocutoffintCount name = pStateF "lfocutoffint" name (maybe 0 (+1)) lfocutoffintCountTo :: String -> Pattern Double -> Pattern ValueMap lfocutoffintCountTo name ipat = innerJoin $ (\i -> pStateF "lfocutoffint" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat lfocutoffintbus :: Pattern Int -> Pattern Double -> ControlPattern lfocutoffintbus busid pat = (pF "lfocutoffint" pat) # (pI "^lfocutoffint" busid) lfocutoffintrecv :: Pattern Int -> ControlPattern lfocutoffintrecv busid = pI "^lfocutoffint" busid -- | lfodelay :: Pattern Double -> ControlPattern lfodelay = pF "lfodelay" lfodelayTake :: String -> [Double] -> ControlPattern lfodelayTake name xs = pStateListF "lfodelay" name xs lfodelayCount :: String -> ControlPattern lfodelayCount name = pStateF "lfodelay" name (maybe 0 (+1)) lfodelayCountTo :: String -> Pattern Double -> Pattern ValueMap lfodelayCountTo name ipat = innerJoin $ (\i -> pStateF "lfodelay" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat lfodelaybus :: Pattern Int -> Pattern Double -> ControlPattern lfodelaybus busid pat = (pF "lfodelay" pat) # (pI "^lfodelay" busid) lfodelayrecv :: Pattern Int -> ControlPattern lfodelayrecv busid = pI "^lfodelay" busid -- | lfoint :: Pattern Double -> ControlPattern lfoint = pF "lfoint" lfointTake :: String -> [Double] -> ControlPattern lfointTake name xs = pStateListF "lfoint" name xs lfointCount :: String -> ControlPattern lfointCount name = pStateF "lfoint" name (maybe 0 (+1)) lfointCountTo :: String -> Pattern Double -> Pattern ValueMap lfointCountTo name ipat = innerJoin $ (\i -> pStateF "lfoint" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat lfointbus :: Pattern Int -> Pattern Double -> ControlPattern lfointbus busid pat = (pF "lfoint" pat) # (pI "^lfoint" busid) lfointrecv :: Pattern Int -> ControlPattern lfointrecv busid = pI "^lfoint" busid -- | lfopitchint :: Pattern Double -> ControlPattern lfopitchint = pF "lfopitchint" lfopitchintTake :: String -> [Double] -> ControlPattern lfopitchintTake name xs = pStateListF "lfopitchint" name xs lfopitchintCount :: String -> ControlPattern lfopitchintCount name = pStateF "lfopitchint" name (maybe 0 (+1)) lfopitchintCountTo :: String -> Pattern Double -> Pattern ValueMap lfopitchintCountTo name ipat = innerJoin $ (\i -> pStateF "lfopitchint" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat lfopitchintbus :: Pattern Int -> Pattern Double -> ControlPattern lfopitchintbus busid pat = (pF "lfopitchint" pat) # (pI "^lfopitchint" busid) lfopitchintrecv :: Pattern Int -> ControlPattern lfopitchintrecv busid = pI "^lfopitchint" busid -- | lfoshape :: Pattern Double -> ControlPattern lfoshape = pF "lfoshape" lfoshapeTake :: String -> [Double] -> ControlPattern lfoshapeTake name xs = pStateListF "lfoshape" name xs lfoshapeCount :: String -> ControlPattern lfoshapeCount name = pStateF "lfoshape" name (maybe 0 (+1)) lfoshapeCountTo :: String -> Pattern Double -> Pattern ValueMap lfoshapeCountTo name ipat = innerJoin $ (\i -> pStateF "lfoshape" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat lfoshapebus :: Pattern Int -> Pattern Double -> ControlPattern lfoshapebus busid pat = (pF "lfoshape" pat) # (pI "^lfoshape" busid) lfoshaperecv :: Pattern Int -> ControlPattern lfoshaperecv busid = pI "^lfoshape" busid -- | lfosync :: Pattern Double -> ControlPattern lfosync = pF "lfosync" lfosyncTake :: String -> [Double] -> ControlPattern lfosyncTake name xs = pStateListF "lfosync" name xs lfosyncCount :: String -> ControlPattern lfosyncCount name = pStateF "lfosync" name (maybe 0 (+1)) lfosyncCountTo :: String -> Pattern Double -> Pattern ValueMap lfosyncCountTo name ipat = innerJoin $ (\i -> pStateF "lfosync" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat lfosyncbus :: Pattern Int -> Pattern Double -> ControlPattern lfosyncbus busid pat = (pF "lfosync" pat) # (pI "^lfosync" busid) lfosyncrecv :: Pattern Int -> ControlPattern lfosyncrecv busid = pI "^lfosync" busid -- | lhitom :: Pattern Double -> ControlPattern lhitom = pF "lhitom" lhitomTake :: String -> [Double] -> ControlPattern lhitomTake name xs = pStateListF "lhitom" name xs lhitomCount :: String -> ControlPattern lhitomCount name = pStateF "lhitom" name (maybe 0 (+1)) lhitomCountTo :: String -> Pattern Double -> Pattern ValueMap lhitomCountTo name ipat = innerJoin $ (\i -> pStateF "lhitom" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat lhitombus :: Pattern Int -> Pattern Double -> ControlPattern lhitombus busid pat = (pF "lhitom" pat) # (pI "^lhitom" busid) lhitomrecv :: Pattern Int -> ControlPattern lhitomrecv busid = pI "^lhitom" busid -- | lkick :: Pattern Double -> ControlPattern lkick = pF "lkick" lkickTake :: String -> [Double] -> ControlPattern lkickTake name xs = pStateListF "lkick" name xs lkickCount :: String -> ControlPattern lkickCount name = pStateF "lkick" name (maybe 0 (+1)) lkickCountTo :: String -> Pattern Double -> Pattern ValueMap lkickCountTo name ipat = innerJoin $ (\i -> pStateF "lkick" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat lkickbus :: Pattern Int -> Pattern Double -> ControlPattern lkickbus busid pat = (pF "lkick" pat) # (pI "^lkick" busid) lkickrecv :: Pattern Int -> ControlPattern lkickrecv busid = pI "^lkick" busid -- | llotom :: Pattern Double -> ControlPattern llotom = pF "llotom" llotomTake :: String -> [Double] -> ControlPattern llotomTake name xs = pStateListF "llotom" name xs llotomCount :: String -> ControlPattern llotomCount name = pStateF "llotom" name (maybe 0 (+1)) llotomCountTo :: String -> Pattern Double -> Pattern ValueMap llotomCountTo name ipat = innerJoin $ (\i -> pStateF "llotom" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat llotombus :: Pattern Int -> Pattern Double -> ControlPattern llotombus busid pat = (pF "llotom" pat) # (pI "^llotom" busid) llotomrecv :: Pattern Int -> ControlPattern llotomrecv busid = pI "^llotom" busid -- | A pattern of numbers. Specifies whether delaytime is calculated relative to cps. When set to 1, delaytime is a direct multiple of a cycle. lock :: Pattern Double -> ControlPattern lock = pF "lock" lockTake :: String -> [Double] -> ControlPattern lockTake name xs = pStateListF "lock" name xs lockCount :: String -> ControlPattern lockCount name = pStateF "lock" name (maybe 0 (+1)) lockCountTo :: String -> Pattern Double -> Pattern ValueMap lockCountTo name ipat = innerJoin $ (\i -> pStateF "lock" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat lockbus :: Pattern Int -> Pattern Double -> ControlPattern lockbus busid pat = (pF "lock" pat) # (pI "^lock" busid) lockrecv :: Pattern Int -> ControlPattern lockrecv busid = pI "^lock" busid -- | loops the sample (from `begin` to `end`) the specified number of times. loop :: Pattern Double -> ControlPattern loop = pF "loop" loopTake :: String -> [Double] -> ControlPattern loopTake name xs = pStateListF "loop" name xs loopCount :: String -> ControlPattern loopCount name = pStateF "loop" name (maybe 0 (+1)) loopCountTo :: String -> Pattern Double -> Pattern ValueMap loopCountTo name ipat = innerJoin $ (\i -> pStateF "loop" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat loopbus :: Pattern Int -> Pattern Double -> ControlPattern loopbus _ _ = error $ "Control parameter 'loop' can't be sent to a bus." -- | lophat :: Pattern Double -> ControlPattern lophat = pF "lophat" lophatTake :: String -> [Double] -> ControlPattern lophatTake name xs = pStateListF "lophat" name xs lophatCount :: String -> ControlPattern lophatCount name = pStateF "lophat" name (maybe 0 (+1)) lophatCountTo :: String -> Pattern Double -> Pattern ValueMap lophatCountTo name ipat = innerJoin $ (\i -> pStateF "lophat" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat lophatbus :: Pattern Int -> Pattern Double -> ControlPattern lophatbus busid pat = (pF "lophat" pat) # (pI "^lophat" busid) lophatrecv :: Pattern Int -> ControlPattern lophatrecv busid = pI "^lophat" busid -- | lrate :: Pattern Double -> ControlPattern lrate = pF "lrate" lrateTake :: String -> [Double] -> ControlPattern lrateTake name xs = pStateListF "lrate" name xs lrateCount :: String -> ControlPattern lrateCount name = pStateF "lrate" name (maybe 0 (+1)) lrateCountTo :: String -> Pattern Double -> Pattern ValueMap lrateCountTo name ipat = innerJoin $ (\i -> pStateF "lrate" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat lratebus :: Pattern Int -> Pattern Double -> ControlPattern lratebus busid pat = (pF "lrate" pat) # (pI "^lrate" busid) lraterecv :: Pattern Int -> ControlPattern lraterecv busid = pI "^lrate" busid -- | lsize :: Pattern Double -> ControlPattern lsize = pF "lsize" lsizeTake :: String -> [Double] -> ControlPattern lsizeTake name xs = pStateListF "lsize" name xs lsizeCount :: String -> ControlPattern lsizeCount name = pStateF "lsize" name (maybe 0 (+1)) lsizeCountTo :: String -> Pattern Double -> Pattern ValueMap lsizeCountTo name ipat = innerJoin $ (\i -> pStateF "lsize" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat lsizebus :: Pattern Int -> Pattern Double -> ControlPattern lsizebus busid pat = (pF "lsize" pat) # (pI "^lsize" busid) lsizerecv :: Pattern Int -> ControlPattern lsizerecv busid = pI "^lsize" busid -- | lsnare :: Pattern Double -> ControlPattern lsnare = pF "lsnare" lsnareTake :: String -> [Double] -> ControlPattern lsnareTake name xs = pStateListF "lsnare" name xs lsnareCount :: String -> ControlPattern lsnareCount name = pStateF "lsnare" name (maybe 0 (+1)) lsnareCountTo :: String -> Pattern Double -> Pattern ValueMap lsnareCountTo name ipat = innerJoin $ (\i -> pStateF "lsnare" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat lsnarebus :: Pattern Int -> Pattern Double -> ControlPattern lsnarebus busid pat = (pF "lsnare" pat) # (pI "^lsnare" busid) lsnarerecv :: Pattern Int -> ControlPattern lsnarerecv busid = pI "^lsnare" busid -- | midibend :: Pattern Double -> ControlPattern midibend = pF "midibend" midibendTake :: String -> [Double] -> ControlPattern midibendTake name xs = pStateListF "midibend" name xs midibendCount :: String -> ControlPattern midibendCount name = pStateF "midibend" name (maybe 0 (+1)) midibendCountTo :: String -> Pattern Double -> Pattern ValueMap midibendCountTo name ipat = innerJoin $ (\i -> pStateF "midibend" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat midibendbus :: Pattern Int -> Pattern Double -> ControlPattern midibendbus _ _ = error $ "Control parameter 'midibend' can't be sent to a bus." -- | midichan :: Pattern Double -> ControlPattern midichan = pF "midichan" midichanTake :: String -> [Double] -> ControlPattern midichanTake name xs = pStateListF "midichan" name xs midichanCount :: String -> ControlPattern midichanCount name = pStateF "midichan" name (maybe 0 (+1)) midichanCountTo :: String -> Pattern Double -> Pattern ValueMap midichanCountTo name ipat = innerJoin $ (\i -> pStateF "midichan" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat midichanbus :: Pattern Int -> Pattern Double -> ControlPattern midichanbus _ _ = error $ "Control parameter 'midichan' can't be sent to a bus." -- | midicmd :: Pattern String -> ControlPattern midicmd = pS "midicmd" midicmdTake :: String -> [Double] -> ControlPattern midicmdTake name xs = pStateListF "midicmd" name xs midicmdbus :: Pattern Int -> Pattern String -> ControlPattern midicmdbus _ _ = error $ "Control parameter 'midicmd' can't be sent to a bus." -- | miditouch :: Pattern Double -> ControlPattern miditouch = pF "miditouch" miditouchTake :: String -> [Double] -> ControlPattern miditouchTake name xs = pStateListF "miditouch" name xs miditouchCount :: String -> ControlPattern miditouchCount name = pStateF "miditouch" name (maybe 0 (+1)) miditouchCountTo :: String -> Pattern Double -> Pattern ValueMap miditouchCountTo name ipat = innerJoin $ (\i -> pStateF "miditouch" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat miditouchbus :: Pattern Int -> Pattern Double -> ControlPattern miditouchbus _ _ = error $ "Control parameter 'miditouch' can't be sent to a bus." -- | minutes :: Pattern Double -> ControlPattern minutes = pF "minutes" minutesTake :: String -> [Double] -> ControlPattern minutesTake name xs = pStateListF "minutes" name xs minutesCount :: String -> ControlPattern minutesCount name = pStateF "minutes" name (maybe 0 (+1)) minutesCountTo :: String -> Pattern Double -> Pattern ValueMap minutesCountTo name ipat = innerJoin $ (\i -> pStateF "minutes" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat minutesbus :: Pattern Int -> Pattern Double -> ControlPattern minutesbus _ _ = error $ "Control parameter 'minutes' can't be sent to a bus." -- | modwheel :: Pattern Double -> ControlPattern modwheel = pF "modwheel" modwheelTake :: String -> [Double] -> ControlPattern modwheelTake name xs = pStateListF "modwheel" name xs modwheelCount :: String -> ControlPattern modwheelCount name = pStateF "modwheel" name (maybe 0 (+1)) modwheelCountTo :: String -> Pattern Double -> Pattern ValueMap modwheelCountTo name ipat = innerJoin $ (\i -> pStateF "modwheel" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat modwheelbus :: Pattern Int -> Pattern Double -> ControlPattern modwheelbus busid pat = (pF "modwheel" pat) # (pI "^modwheel" busid) modwheelrecv :: Pattern Int -> ControlPattern modwheelrecv busid = pI "^modwheel" busid -- | mtranspose :: Pattern Double -> ControlPattern mtranspose = pF "mtranspose" mtransposeTake :: String -> [Double] -> ControlPattern mtransposeTake name xs = pStateListF "mtranspose" name xs mtransposeCount :: String -> ControlPattern mtransposeCount name = pStateF "mtranspose" name (maybe 0 (+1)) mtransposeCountTo :: String -> Pattern Double -> Pattern ValueMap mtransposeCountTo name ipat = innerJoin $ (\i -> pStateF "mtranspose" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat mtransposebus :: Pattern Int -> Pattern Double -> ControlPattern mtransposebus busid pat = (pF "mtranspose" pat) # (pI "^mtranspose" busid) mtransposerecv :: Pattern Int -> ControlPattern mtransposerecv busid = pI "^mtranspose" busid -- | The note or sample number to choose for a synth or sampleset n :: Pattern Note -> ControlPattern n = pN "n" nTake :: String -> [Double] -> ControlPattern nTake name xs = pStateListF "n" name xs nCount :: String -> ControlPattern nCount name = pStateF "n" name (maybe 0 (+1)) nCountTo :: String -> Pattern Double -> Pattern ValueMap nCountTo name ipat = innerJoin $ (\i -> pStateF "n" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat nbus :: Pattern Int -> Pattern Note -> ControlPattern nbus _ _ = error $ "Control parameter 'n' can't be sent to a bus." -- | The note or pitch to play a sound or synth with note :: Pattern Note -> ControlPattern note = pN "note" noteTake :: String -> [Double] -> ControlPattern noteTake name xs = pStateListF "note" name xs noteCount :: String -> ControlPattern noteCount name = pStateF "note" name (maybe 0 (+1)) noteCountTo :: String -> Pattern Double -> Pattern ValueMap noteCountTo name ipat = innerJoin $ (\i -> pStateF "note" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat notebus :: Pattern Int -> Pattern Note -> ControlPattern notebus _ _ = error $ "Control parameter 'note' can't be sent to a bus." -- | Nudges events into the future by the specified number of seconds. Negative numbers work up to a point as well (due to internal latency) nudge :: Pattern Double -> ControlPattern nudge = pF "nudge" nudgeTake :: String -> [Double] -> ControlPattern nudgeTake name xs = pStateListF "nudge" name xs nudgeCount :: String -> ControlPattern nudgeCount name = pStateF "nudge" name (maybe 0 (+1)) nudgeCountTo :: String -> Pattern Double -> Pattern ValueMap nudgeCountTo name ipat = innerJoin $ (\i -> pStateF "nudge" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat nudgebus :: Pattern Int -> Pattern Double -> ControlPattern nudgebus busid pat = (pF "nudge" pat) # (pI "^nudge" busid) nudgerecv :: Pattern Int -> ControlPattern nudgerecv busid = pI "^nudge" busid -- | octave :: Pattern Int -> ControlPattern octave = pI "octave" octaveTake :: String -> [Double] -> ControlPattern octaveTake name xs = pStateListF "octave" name xs octaveCount :: String -> ControlPattern octaveCount name = pStateF "octave" name (maybe 0 (+1)) octaveCountTo :: String -> Pattern Double -> Pattern ValueMap octaveCountTo name ipat = innerJoin $ (\i -> pStateF "octave" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat octavebus :: Pattern Int -> Pattern Int -> ControlPattern octavebus _ _ = error $ "Control parameter 'octave' can't be sent to a bus." -- | octaveR :: Pattern Double -> ControlPattern octaveR = pF "octaveR" octaveRTake :: String -> [Double] -> ControlPattern octaveRTake name xs = pStateListF "octaveR" name xs octaveRCount :: String -> ControlPattern octaveRCount name = pStateF "octaveR" name (maybe 0 (+1)) octaveRCountTo :: String -> Pattern Double -> Pattern ValueMap octaveRCountTo name ipat = innerJoin $ (\i -> pStateF "octaveR" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat octaveRbus :: Pattern Int -> Pattern Double -> ControlPattern octaveRbus busid pat = (pF "octaveR" pat) # (pI "^octaveR" busid) octaveRrecv :: Pattern Int -> ControlPattern octaveRrecv busid = pI "^octaveR" busid -- | octaver effect octer :: Pattern Double -> ControlPattern octer = pF "octer" octerTake :: String -> [Double] -> ControlPattern octerTake name xs = pStateListF "octer" name xs octerCount :: String -> ControlPattern octerCount name = pStateF "octer" name (maybe 0 (+1)) octerCountTo :: String -> Pattern Double -> Pattern ValueMap octerCountTo name ipat = innerJoin $ (\i -> pStateF "octer" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat octerbus :: Pattern Int -> Pattern Double -> ControlPattern octerbus busid pat = (pF "octer" pat) # (pI "^octer" busid) octerrecv :: Pattern Int -> ControlPattern octerrecv busid = pI "^octer" busid -- | octaver effect octersub :: Pattern Double -> ControlPattern octersub = pF "octersub" octersubTake :: String -> [Double] -> ControlPattern octersubTake name xs = pStateListF "octersub" name xs octersubCount :: String -> ControlPattern octersubCount name = pStateF "octersub" name (maybe 0 (+1)) octersubCountTo :: String -> Pattern Double -> Pattern ValueMap octersubCountTo name ipat = innerJoin $ (\i -> pStateF "octersub" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat octersubbus :: Pattern Int -> Pattern Double -> ControlPattern octersubbus busid pat = (pF "octersub" pat) # (pI "^octersub" busid) octersubrecv :: Pattern Int -> ControlPattern octersubrecv busid = pI "^octersub" busid -- | octaver effect octersubsub :: Pattern Double -> ControlPattern octersubsub = pF "octersubsub" octersubsubTake :: String -> [Double] -> ControlPattern octersubsubTake name xs = pStateListF "octersubsub" name xs octersubsubCount :: String -> ControlPattern octersubsubCount name = pStateF "octersubsub" name (maybe 0 (+1)) octersubsubCountTo :: String -> Pattern Double -> Pattern ValueMap octersubsubCountTo name ipat = innerJoin $ (\i -> pStateF "octersubsub" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat octersubsubbus :: Pattern Int -> Pattern Double -> ControlPattern octersubsubbus busid pat = (pF "octersubsub" pat) # (pI "^octersubsub" busid) octersubsubrecv :: Pattern Int -> ControlPattern octersubsubrecv busid = pI "^octersubsub" busid -- | offset :: Pattern Double -> ControlPattern offset = pF "offset" offsetTake :: String -> [Double] -> ControlPattern offsetTake name xs = pStateListF "offset" name xs offsetCount :: String -> ControlPattern offsetCount name = pStateF "offset" name (maybe 0 (+1)) offsetCountTo :: String -> Pattern Double -> Pattern ValueMap offsetCountTo name ipat = innerJoin $ (\i -> pStateF "offset" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat offsetbus :: Pattern Int -> Pattern Double -> ControlPattern offsetbus _ _ = error $ "Control parameter 'offset' can't be sent to a bus." -- | ophatdecay :: Pattern Double -> ControlPattern ophatdecay = pF "ophatdecay" ophatdecayTake :: String -> [Double] -> ControlPattern ophatdecayTake name xs = pStateListF "ophatdecay" name xs ophatdecayCount :: String -> ControlPattern ophatdecayCount name = pStateF "ophatdecay" name (maybe 0 (+1)) ophatdecayCountTo :: String -> Pattern Double -> Pattern ValueMap ophatdecayCountTo name ipat = innerJoin $ (\i -> pStateF "ophatdecay" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat ophatdecaybus :: Pattern Int -> Pattern Double -> ControlPattern ophatdecaybus busid pat = (pF "ophatdecay" pat) # (pI "^ophatdecay" busid) ophatdecayrecv :: Pattern Int -> ControlPattern ophatdecayrecv busid = pI "^ophatdecay" busid -- | a pattern of numbers. An `orbit` is a global parameter context for patterns. Patterns with the same orbit will share hardware output bus offset and global effects, e.g. reverb and delay. The maximum number of orbits is specified in the superdirt startup, numbers higher than maximum will wrap around. orbit :: Pattern Int -> ControlPattern orbit = pI "orbit" orbitTake :: String -> [Double] -> ControlPattern orbitTake name xs = pStateListF "orbit" name xs orbitCount :: String -> ControlPattern orbitCount name = pStateF "orbit" name (maybe 0 (+1)) orbitCountTo :: String -> Pattern Double -> Pattern ValueMap orbitCountTo name ipat = innerJoin $ (\i -> pStateF "orbit" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat orbitbus :: Pattern Int -> Pattern Int -> ControlPattern orbitbus busid pat = (pI "orbit" pat) # (pI "^orbit" busid) orbitrecv :: Pattern Int -> ControlPattern orbitrecv busid = pI "^orbit" busid -- | overgain :: Pattern Double -> ControlPattern overgain = pF "overgain" overgainTake :: String -> [Double] -> ControlPattern overgainTake name xs = pStateListF "overgain" name xs overgainCount :: String -> ControlPattern overgainCount name = pStateF "overgain" name (maybe 0 (+1)) overgainCountTo :: String -> Pattern Double -> Pattern ValueMap overgainCountTo name ipat = innerJoin $ (\i -> pStateF "overgain" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat overgainbus :: Pattern Int -> Pattern Double -> ControlPattern overgainbus _ _ = error $ "Control parameter 'overgain' can't be sent to a bus." -- | overshape :: Pattern Double -> ControlPattern overshape = pF "overshape" overshapeTake :: String -> [Double] -> ControlPattern overshapeTake name xs = pStateListF "overshape" name xs overshapeCount :: String -> ControlPattern overshapeCount name = pStateF "overshape" name (maybe 0 (+1)) overshapeCountTo :: String -> Pattern Double -> Pattern ValueMap overshapeCountTo name ipat = innerJoin $ (\i -> pStateF "overshape" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat overshapebus :: Pattern Int -> Pattern Double -> ControlPattern overshapebus busid pat = (pF "overshape" pat) # (pI "^overshape" busid) overshaperecv :: Pattern Int -> ControlPattern overshaperecv busid = pI "^overshape" busid -- | a pattern of numbers between 0 and 1, from left to right (assuming stereo), once round a circle (assuming multichannel) pan :: Pattern Double -> ControlPattern pan = pF "pan" panTake :: String -> [Double] -> ControlPattern panTake name xs = pStateListF "pan" name xs panCount :: String -> ControlPattern panCount name = pStateF "pan" name (maybe 0 (+1)) panCountTo :: String -> Pattern Double -> Pattern ValueMap panCountTo name ipat = innerJoin $ (\i -> pStateF "pan" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat panbus :: Pattern Int -> Pattern Double -> ControlPattern panbus busid pat = (pF "pan" pat) # (pI "^pan" busid) panrecv :: Pattern Int -> ControlPattern panrecv busid = pI "^pan" busid -- | a pattern of numbers between -1.0 and 1.0, which controls the relative position of the centre pan in a pair of adjacent speakers (multichannel only) panorient :: Pattern Double -> ControlPattern panorient = pF "panorient" panorientTake :: String -> [Double] -> ControlPattern panorientTake name xs = pStateListF "panorient" name xs panorientCount :: String -> ControlPattern panorientCount name = pStateF "panorient" name (maybe 0 (+1)) panorientCountTo :: String -> Pattern Double -> Pattern ValueMap panorientCountTo name ipat = innerJoin $ (\i -> pStateF "panorient" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat panorientbus :: Pattern Int -> Pattern Double -> ControlPattern panorientbus busid pat = (pF "panorient" pat) # (pI "^panorient" busid) panorientrecv :: Pattern Int -> ControlPattern panorientrecv busid = pI "^panorient" busid -- | a pattern of numbers between -inf and inf, which controls how much multichannel output is fanned out (negative is backwards ordering) panspan :: Pattern Double -> ControlPattern panspan = pF "panspan" panspanTake :: String -> [Double] -> ControlPattern panspanTake name xs = pStateListF "panspan" name xs panspanCount :: String -> ControlPattern panspanCount name = pStateF "panspan" name (maybe 0 (+1)) panspanCountTo :: String -> Pattern Double -> Pattern ValueMap panspanCountTo name ipat = innerJoin $ (\i -> pStateF "panspan" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat panspanbus :: Pattern Int -> Pattern Double -> ControlPattern panspanbus busid pat = (pF "panspan" pat) # (pI "^panspan" busid) panspanrecv :: Pattern Int -> ControlPattern panspanrecv busid = pI "^panspan" busid -- | a pattern of numbers between 0.0 and 1.0, which controls the multichannel spread range (multichannel only) pansplay :: Pattern Double -> ControlPattern pansplay = pF "pansplay" pansplayTake :: String -> [Double] -> ControlPattern pansplayTake name xs = pStateListF "pansplay" name xs pansplayCount :: String -> ControlPattern pansplayCount name = pStateF "pansplay" name (maybe 0 (+1)) pansplayCountTo :: String -> Pattern Double -> Pattern ValueMap pansplayCountTo name ipat = innerJoin $ (\i -> pStateF "pansplay" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat pansplaybus :: Pattern Int -> Pattern Double -> ControlPattern pansplaybus busid pat = (pF "pansplay" pat) # (pI "^pansplay" busid) pansplayrecv :: Pattern Int -> ControlPattern pansplayrecv busid = pI "^pansplay" busid -- | a pattern of numbers between 0.0 and inf, which controls how much each channel is distributed over neighbours (multichannel only) panwidth :: Pattern Double -> ControlPattern panwidth = pF "panwidth" panwidthTake :: String -> [Double] -> ControlPattern panwidthTake name xs = pStateListF "panwidth" name xs panwidthCount :: String -> ControlPattern panwidthCount name = pStateF "panwidth" name (maybe 0 (+1)) panwidthCountTo :: String -> Pattern Double -> Pattern ValueMap panwidthCountTo name ipat = innerJoin $ (\i -> pStateF "panwidth" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat panwidthbus :: Pattern Int -> Pattern Double -> ControlPattern panwidthbus busid pat = (pF "panwidth" pat) # (pI "^panwidth" busid) panwidthrecv :: Pattern Int -> ControlPattern panwidthrecv busid = pI "^panwidth" busid -- | partials :: Pattern Double -> ControlPattern partials = pF "partials" partialsTake :: String -> [Double] -> ControlPattern partialsTake name xs = pStateListF "partials" name xs partialsCount :: String -> ControlPattern partialsCount name = pStateF "partials" name (maybe 0 (+1)) partialsCountTo :: String -> Pattern Double -> Pattern ValueMap partialsCountTo name ipat = innerJoin $ (\i -> pStateF "partials" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat partialsbus :: Pattern Int -> Pattern Double -> ControlPattern partialsbus busid pat = (pF "partials" pat) # (pI "^partials" busid) partialsrecv :: Pattern Int -> ControlPattern partialsrecv busid = pI "^partials" busid -- | Phaser Audio DSP effect | params are 'phaserrate' and 'phaserdepth' phaserdepth :: Pattern Double -> ControlPattern phaserdepth = pF "phaserdepth" phaserdepthTake :: String -> [Double] -> ControlPattern phaserdepthTake name xs = pStateListF "phaserdepth" name xs phaserdepthCount :: String -> ControlPattern phaserdepthCount name = pStateF "phaserdepth" name (maybe 0 (+1)) phaserdepthCountTo :: String -> Pattern Double -> Pattern ValueMap phaserdepthCountTo name ipat = innerJoin $ (\i -> pStateF "phaserdepth" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat phaserdepthbus :: Pattern Int -> Pattern Double -> ControlPattern phaserdepthbus busid pat = (pF "phaserdepth" pat) # (pI "^phaserdepth" busid) phaserdepthrecv :: Pattern Int -> ControlPattern phaserdepthrecv busid = pI "^phaserdepth" busid -- | Phaser Audio DSP effect | params are 'phaserrate' and 'phaserdepth' phaserrate :: Pattern Double -> ControlPattern phaserrate = pF "phaserrate" phaserrateTake :: String -> [Double] -> ControlPattern phaserrateTake name xs = pStateListF "phaserrate" name xs phaserrateCount :: String -> ControlPattern phaserrateCount name = pStateF "phaserrate" name (maybe 0 (+1)) phaserrateCountTo :: String -> Pattern Double -> Pattern ValueMap phaserrateCountTo name ipat = innerJoin $ (\i -> pStateF "phaserrate" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat phaserratebus :: Pattern Int -> Pattern Double -> ControlPattern phaserratebus busid pat = (pF "phaserrate" pat) # (pI "^phaserrate" busid) phaserraterecv :: Pattern Int -> ControlPattern phaserraterecv busid = pI "^phaserrate" busid -- | pitch1 :: Pattern Double -> ControlPattern pitch1 = pF "pitch1" pitch1Take :: String -> [Double] -> ControlPattern pitch1Take name xs = pStateListF "pitch1" name xs pitch1Count :: String -> ControlPattern pitch1Count name = pStateF "pitch1" name (maybe 0 (+1)) pitch1CountTo :: String -> Pattern Double -> Pattern ValueMap pitch1CountTo name ipat = innerJoin $ (\i -> pStateF "pitch1" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat pitch1bus :: Pattern Int -> Pattern Double -> ControlPattern pitch1bus busid pat = (pF "pitch1" pat) # (pI "^pitch1" busid) pitch1recv :: Pattern Int -> ControlPattern pitch1recv busid = pI "^pitch1" busid -- | pitch2 :: Pattern Double -> ControlPattern pitch2 = pF "pitch2" pitch2Take :: String -> [Double] -> ControlPattern pitch2Take name xs = pStateListF "pitch2" name xs pitch2Count :: String -> ControlPattern pitch2Count name = pStateF "pitch2" name (maybe 0 (+1)) pitch2CountTo :: String -> Pattern Double -> Pattern ValueMap pitch2CountTo name ipat = innerJoin $ (\i -> pStateF "pitch2" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat pitch2bus :: Pattern Int -> Pattern Double -> ControlPattern pitch2bus busid pat = (pF "pitch2" pat) # (pI "^pitch2" busid) pitch2recv :: Pattern Int -> ControlPattern pitch2recv busid = pI "^pitch2" busid -- | pitch3 :: Pattern Double -> ControlPattern pitch3 = pF "pitch3" pitch3Take :: String -> [Double] -> ControlPattern pitch3Take name xs = pStateListF "pitch3" name xs pitch3Count :: String -> ControlPattern pitch3Count name = pStateF "pitch3" name (maybe 0 (+1)) pitch3CountTo :: String -> Pattern Double -> Pattern ValueMap pitch3CountTo name ipat = innerJoin $ (\i -> pStateF "pitch3" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat pitch3bus :: Pattern Int -> Pattern Double -> ControlPattern pitch3bus busid pat = (pF "pitch3" pat) # (pI "^pitch3" busid) pitch3recv :: Pattern Int -> ControlPattern pitch3recv busid = pI "^pitch3" busid -- | polyTouch :: Pattern Double -> ControlPattern polyTouch = pF "polyTouch" polyTouchTake :: String -> [Double] -> ControlPattern polyTouchTake name xs = pStateListF "polyTouch" name xs polyTouchCount :: String -> ControlPattern polyTouchCount name = pStateF "polyTouch" name (maybe 0 (+1)) polyTouchCountTo :: String -> Pattern Double -> Pattern ValueMap polyTouchCountTo name ipat = innerJoin $ (\i -> pStateF "polyTouch" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat polyTouchbus :: Pattern Int -> Pattern Double -> ControlPattern polyTouchbus _ _ = error $ "Control parameter 'polyTouch' can't be sent to a bus." -- | portamento :: Pattern Double -> ControlPattern portamento = pF "portamento" portamentoTake :: String -> [Double] -> ControlPattern portamentoTake name xs = pStateListF "portamento" name xs portamentoCount :: String -> ControlPattern portamentoCount name = pStateF "portamento" name (maybe 0 (+1)) portamentoCountTo :: String -> Pattern Double -> Pattern ValueMap portamentoCountTo name ipat = innerJoin $ (\i -> pStateF "portamento" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat portamentobus :: Pattern Int -> Pattern Double -> ControlPattern portamentobus busid pat = (pF "portamento" pat) # (pI "^portamento" busid) portamentorecv :: Pattern Int -> ControlPattern portamentorecv busid = pI "^portamento" busid -- | progNum :: Pattern Double -> ControlPattern progNum = pF "progNum" progNumTake :: String -> [Double] -> ControlPattern progNumTake name xs = pStateListF "progNum" name xs progNumCount :: String -> ControlPattern progNumCount name = pStateF "progNum" name (maybe 0 (+1)) progNumCountTo :: String -> Pattern Double -> Pattern ValueMap progNumCountTo name ipat = innerJoin $ (\i -> pStateF "progNum" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat progNumbus :: Pattern Int -> Pattern Double -> ControlPattern progNumbus _ _ = error $ "Control parameter 'progNum' can't be sent to a bus." -- | used in SuperDirt softsynths as a control rate or 'speed' rate :: Pattern Double -> ControlPattern rate = pF "rate" rateTake :: String -> [Double] -> ControlPattern rateTake name xs = pStateListF "rate" name xs rateCount :: String -> ControlPattern rateCount name = pStateF "rate" name (maybe 0 (+1)) rateCountTo :: String -> Pattern Double -> Pattern ValueMap rateCountTo name ipat = innerJoin $ (\i -> pStateF "rate" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat ratebus :: Pattern Int -> Pattern Double -> ControlPattern ratebus busid pat = (pF "rate" pat) # (pI "^rate" busid) raterecv :: Pattern Int -> ControlPattern raterecv busid = pI "^rate" busid -- | Spectral conform real :: Pattern Double -> ControlPattern real = pF "real" realTake :: String -> [Double] -> ControlPattern realTake name xs = pStateListF "real" name xs realCount :: String -> ControlPattern realCount name = pStateF "real" name (maybe 0 (+1)) realCountTo :: String -> Pattern Double -> Pattern ValueMap realCountTo name ipat = innerJoin $ (\i -> pStateF "real" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat realbus :: Pattern Int -> Pattern Double -> ControlPattern realbus busid pat = (pF "real" pat) # (pI "^real" busid) realrecv :: Pattern Int -> ControlPattern realrecv busid = pI "^real" busid -- | a pattern of numbers to specify the release time (in seconds) of an envelope applied to each sample. release :: Pattern Double -> ControlPattern release = pF "release" releaseTake :: String -> [Double] -> ControlPattern releaseTake name xs = pStateListF "release" name xs releaseCount :: String -> ControlPattern releaseCount name = pStateF "release" name (maybe 0 (+1)) releaseCountTo :: String -> Pattern Double -> Pattern ValueMap releaseCountTo name ipat = innerJoin $ (\i -> pStateF "release" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat releasebus :: Pattern Int -> Pattern Double -> ControlPattern releasebus busid pat = (pF "release" pat) # (pI "^release" busid) releaserecv :: Pattern Int -> ControlPattern releaserecv busid = pI "^release" busid -- | a pattern of numbers from 0 to 1. Specifies the resonance of the low-pass filter. resonance :: Pattern Double -> ControlPattern resonance = pF "resonance" resonanceTake :: String -> [Double] -> ControlPattern resonanceTake name xs = pStateListF "resonance" name xs resonanceCount :: String -> ControlPattern resonanceCount name = pStateF "resonance" name (maybe 0 (+1)) resonanceCountTo :: String -> Pattern Double -> Pattern ValueMap resonanceCountTo name ipat = innerJoin $ (\i -> pStateF "resonance" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat resonancebus :: Pattern Int -> Pattern Double -> ControlPattern resonancebus busid pat = (pF "resonance" pat) # (pI "^resonance" busid) resonancerecv :: Pattern Int -> ControlPattern resonancerecv busid = pI "^resonance" busid -- | ring modulation ring :: Pattern Double -> ControlPattern ring = pF "ring" ringTake :: String -> [Double] -> ControlPattern ringTake name xs = pStateListF "ring" name xs ringCount :: String -> ControlPattern ringCount name = pStateF "ring" name (maybe 0 (+1)) ringCountTo :: String -> Pattern Double -> Pattern ValueMap ringCountTo name ipat = innerJoin $ (\i -> pStateF "ring" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat ringbus :: Pattern Int -> Pattern Double -> ControlPattern ringbus busid pat = (pF "ring" pat) # (pI "^ring" busid) ringrecv :: Pattern Int -> ControlPattern ringrecv busid = pI "^ring" busid -- | ring modulation ringdf :: Pattern Double -> ControlPattern ringdf = pF "ringdf" ringdfTake :: String -> [Double] -> ControlPattern ringdfTake name xs = pStateListF "ringdf" name xs ringdfCount :: String -> ControlPattern ringdfCount name = pStateF "ringdf" name (maybe 0 (+1)) ringdfCountTo :: String -> Pattern Double -> Pattern ValueMap ringdfCountTo name ipat = innerJoin $ (\i -> pStateF "ringdf" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat ringdfbus :: Pattern Int -> Pattern Double -> ControlPattern ringdfbus busid pat = (pF "ringdf" pat) # (pI "^ringdf" busid) ringdfrecv :: Pattern Int -> ControlPattern ringdfrecv busid = pI "^ringdf" busid -- | ring modulation ringf :: Pattern Double -> ControlPattern ringf = pF "ringf" ringfTake :: String -> [Double] -> ControlPattern ringfTake name xs = pStateListF "ringf" name xs ringfCount :: String -> ControlPattern ringfCount name = pStateF "ringf" name (maybe 0 (+1)) ringfCountTo :: String -> Pattern Double -> Pattern ValueMap ringfCountTo name ipat = innerJoin $ (\i -> pStateF "ringf" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat ringfbus :: Pattern Int -> Pattern Double -> ControlPattern ringfbus busid pat = (pF "ringf" pat) # (pI "^ringf" busid) ringfrecv :: Pattern Int -> ControlPattern ringfrecv busid = pI "^ringf" busid -- | a pattern of numbers from 0 to 1. Sets the level of reverb. room :: Pattern Double -> ControlPattern room = pF "room" roomTake :: String -> [Double] -> ControlPattern roomTake name xs = pStateListF "room" name xs roomCount :: String -> ControlPattern roomCount name = pStateF "room" name (maybe 0 (+1)) roomCountTo :: String -> Pattern Double -> Pattern ValueMap roomCountTo name ipat = innerJoin $ (\i -> pStateF "room" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat roombus :: Pattern Int -> Pattern Double -> ControlPattern roombus busid pat = (pF "room" pat) # (pI "^room" busid) roomrecv :: Pattern Int -> ControlPattern roomrecv busid = pI "^room" busid -- | sagogo :: Pattern Double -> ControlPattern sagogo = pF "sagogo" sagogoTake :: String -> [Double] -> ControlPattern sagogoTake name xs = pStateListF "sagogo" name xs sagogoCount :: String -> ControlPattern sagogoCount name = pStateF "sagogo" name (maybe 0 (+1)) sagogoCountTo :: String -> Pattern Double -> Pattern ValueMap sagogoCountTo name ipat = innerJoin $ (\i -> pStateF "sagogo" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat sagogobus :: Pattern Int -> Pattern Double -> ControlPattern sagogobus busid pat = (pF "sagogo" pat) # (pI "^sagogo" busid) sagogorecv :: Pattern Int -> ControlPattern sagogorecv busid = pI "^sagogo" busid -- | sclap :: Pattern Double -> ControlPattern sclap = pF "sclap" sclapTake :: String -> [Double] -> ControlPattern sclapTake name xs = pStateListF "sclap" name xs sclapCount :: String -> ControlPattern sclapCount name = pStateF "sclap" name (maybe 0 (+1)) sclapCountTo :: String -> Pattern Double -> Pattern ValueMap sclapCountTo name ipat = innerJoin $ (\i -> pStateF "sclap" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat sclapbus :: Pattern Int -> Pattern Double -> ControlPattern sclapbus busid pat = (pF "sclap" pat) # (pI "^sclap" busid) sclaprecv :: Pattern Int -> ControlPattern sclaprecv busid = pI "^sclap" busid -- | sclaves :: Pattern Double -> ControlPattern sclaves = pF "sclaves" sclavesTake :: String -> [Double] -> ControlPattern sclavesTake name xs = pStateListF "sclaves" name xs sclavesCount :: String -> ControlPattern sclavesCount name = pStateF "sclaves" name (maybe 0 (+1)) sclavesCountTo :: String -> Pattern Double -> Pattern ValueMap sclavesCountTo name ipat = innerJoin $ (\i -> pStateF "sclaves" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat sclavesbus :: Pattern Int -> Pattern Double -> ControlPattern sclavesbus busid pat = (pF "sclaves" pat) # (pI "^sclaves" busid) sclavesrecv :: Pattern Int -> ControlPattern sclavesrecv busid = pI "^sclaves" busid -- | Spectral scramble scram :: Pattern Double -> ControlPattern scram = pF "scram" scramTake :: String -> [Double] -> ControlPattern scramTake name xs = pStateListF "scram" name xs scramCount :: String -> ControlPattern scramCount name = pStateF "scram" name (maybe 0 (+1)) scramCountTo :: String -> Pattern Double -> Pattern ValueMap scramCountTo name ipat = innerJoin $ (\i -> pStateF "scram" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat scrambus :: Pattern Int -> Pattern Double -> ControlPattern scrambus busid pat = (pF "scram" pat) # (pI "^scram" busid) scramrecv :: Pattern Int -> ControlPattern scramrecv busid = pI "^scram" busid -- | scrash :: Pattern Double -> ControlPattern scrash = pF "scrash" scrashTake :: String -> [Double] -> ControlPattern scrashTake name xs = pStateListF "scrash" name xs scrashCount :: String -> ControlPattern scrashCount name = pStateF "scrash" name (maybe 0 (+1)) scrashCountTo :: String -> Pattern Double -> Pattern ValueMap scrashCountTo name ipat = innerJoin $ (\i -> pStateF "scrash" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat scrashbus :: Pattern Int -> Pattern Double -> ControlPattern scrashbus busid pat = (pF "scrash" pat) # (pI "^scrash" busid) scrashrecv :: Pattern Int -> ControlPattern scrashrecv busid = pI "^scrash" busid -- | seconds :: Pattern Double -> ControlPattern seconds = pF "seconds" secondsTake :: String -> [Double] -> ControlPattern secondsTake name xs = pStateListF "seconds" name xs secondsCount :: String -> ControlPattern secondsCount name = pStateF "seconds" name (maybe 0 (+1)) secondsCountTo :: String -> Pattern Double -> Pattern ValueMap secondsCountTo name ipat = innerJoin $ (\i -> pStateF "seconds" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat secondsbus :: Pattern Int -> Pattern Double -> ControlPattern secondsbus _ _ = error $ "Control parameter 'seconds' can't be sent to a bus." -- | semitone :: Pattern Double -> ControlPattern semitone = pF "semitone" semitoneTake :: String -> [Double] -> ControlPattern semitoneTake name xs = pStateListF "semitone" name xs semitoneCount :: String -> ControlPattern semitoneCount name = pStateF "semitone" name (maybe 0 (+1)) semitoneCountTo :: String -> Pattern Double -> Pattern ValueMap semitoneCountTo name ipat = innerJoin $ (\i -> pStateF "semitone" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat semitonebus :: Pattern Int -> Pattern Double -> ControlPattern semitonebus busid pat = (pF "semitone" pat) # (pI "^semitone" busid) semitonerecv :: Pattern Int -> ControlPattern semitonerecv busid = pI "^semitone" busid -- | wave shaping distortion, a pattern of numbers from 0 for no distortion up to 1 for loads of distortion. shape :: Pattern Double -> ControlPattern shape = pF "shape" shapeTake :: String -> [Double] -> ControlPattern shapeTake name xs = pStateListF "shape" name xs shapeCount :: String -> ControlPattern shapeCount name = pStateF "shape" name (maybe 0 (+1)) shapeCountTo :: String -> Pattern Double -> Pattern ValueMap shapeCountTo name ipat = innerJoin $ (\i -> pStateF "shape" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat shapebus :: Pattern Int -> Pattern Double -> ControlPattern shapebus busid pat = (pF "shape" pat) # (pI "^shape" busid) shaperecv :: Pattern Int -> ControlPattern shaperecv busid = pI "^shape" busid -- | a pattern of numbers from 0 to 1. Sets the perceptual size (reverb time) of the `room` to be used in reverb. size :: Pattern Double -> ControlPattern size = pF "size" sizeTake :: String -> [Double] -> ControlPattern sizeTake name xs = pStateListF "size" name xs sizeCount :: String -> ControlPattern sizeCount name = pStateF "size" name (maybe 0 (+1)) sizeCountTo :: String -> Pattern Double -> Pattern ValueMap sizeCountTo name ipat = innerJoin $ (\i -> pStateF "size" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat sizebus :: Pattern Int -> Pattern Double -> ControlPattern sizebus busid pat = (pF "size" pat) # (pI "^size" busid) sizerecv :: Pattern Int -> ControlPattern sizerecv busid = pI "^size" busid -- | slide :: Pattern Double -> ControlPattern slide = pF "slide" slideTake :: String -> [Double] -> ControlPattern slideTake name xs = pStateListF "slide" name xs slideCount :: String -> ControlPattern slideCount name = pStateF "slide" name (maybe 0 (+1)) slideCountTo :: String -> Pattern Double -> Pattern ValueMap slideCountTo name ipat = innerJoin $ (\i -> pStateF "slide" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat slidebus :: Pattern Int -> Pattern Double -> ControlPattern slidebus busid pat = (pF "slide" pat) # (pI "^slide" busid) sliderecv :: Pattern Int -> ControlPattern sliderecv busid = pI "^slide" busid -- | slider0 :: Pattern Double -> ControlPattern slider0 = pF "slider0" slider0Take :: String -> [Double] -> ControlPattern slider0Take name xs = pStateListF "slider0" name xs slider0Count :: String -> ControlPattern slider0Count name = pStateF "slider0" name (maybe 0 (+1)) slider0CountTo :: String -> Pattern Double -> Pattern ValueMap slider0CountTo name ipat = innerJoin $ (\i -> pStateF "slider0" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat slider0bus :: Pattern Int -> Pattern Double -> ControlPattern slider0bus busid pat = (pF "slider0" pat) # (pI "^slider0" busid) slider0recv :: Pattern Int -> ControlPattern slider0recv busid = pI "^slider0" busid -- | slider1 :: Pattern Double -> ControlPattern slider1 = pF "slider1" slider1Take :: String -> [Double] -> ControlPattern slider1Take name xs = pStateListF "slider1" name xs slider1Count :: String -> ControlPattern slider1Count name = pStateF "slider1" name (maybe 0 (+1)) slider1CountTo :: String -> Pattern Double -> Pattern ValueMap slider1CountTo name ipat = innerJoin $ (\i -> pStateF "slider1" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat slider1bus :: Pattern Int -> Pattern Double -> ControlPattern slider1bus busid pat = (pF "slider1" pat) # (pI "^slider1" busid) slider1recv :: Pattern Int -> ControlPattern slider1recv busid = pI "^slider1" busid -- | slider10 :: Pattern Double -> ControlPattern slider10 = pF "slider10" slider10Take :: String -> [Double] -> ControlPattern slider10Take name xs = pStateListF "slider10" name xs slider10Count :: String -> ControlPattern slider10Count name = pStateF "slider10" name (maybe 0 (+1)) slider10CountTo :: String -> Pattern Double -> Pattern ValueMap slider10CountTo name ipat = innerJoin $ (\i -> pStateF "slider10" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat slider10bus :: Pattern Int -> Pattern Double -> ControlPattern slider10bus busid pat = (pF "slider10" pat) # (pI "^slider10" busid) slider10recv :: Pattern Int -> ControlPattern slider10recv busid = pI "^slider10" busid -- | slider11 :: Pattern Double -> ControlPattern slider11 = pF "slider11" slider11Take :: String -> [Double] -> ControlPattern slider11Take name xs = pStateListF "slider11" name xs slider11Count :: String -> ControlPattern slider11Count name = pStateF "slider11" name (maybe 0 (+1)) slider11CountTo :: String -> Pattern Double -> Pattern ValueMap slider11CountTo name ipat = innerJoin $ (\i -> pStateF "slider11" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat slider11bus :: Pattern Int -> Pattern Double -> ControlPattern slider11bus busid pat = (pF "slider11" pat) # (pI "^slider11" busid) slider11recv :: Pattern Int -> ControlPattern slider11recv busid = pI "^slider11" busid -- | slider12 :: Pattern Double -> ControlPattern slider12 = pF "slider12" slider12Take :: String -> [Double] -> ControlPattern slider12Take name xs = pStateListF "slider12" name xs slider12Count :: String -> ControlPattern slider12Count name = pStateF "slider12" name (maybe 0 (+1)) slider12CountTo :: String -> Pattern Double -> Pattern ValueMap slider12CountTo name ipat = innerJoin $ (\i -> pStateF "slider12" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat slider12bus :: Pattern Int -> Pattern Double -> ControlPattern slider12bus busid pat = (pF "slider12" pat) # (pI "^slider12" busid) slider12recv :: Pattern Int -> ControlPattern slider12recv busid = pI "^slider12" busid -- | slider13 :: Pattern Double -> ControlPattern slider13 = pF "slider13" slider13Take :: String -> [Double] -> ControlPattern slider13Take name xs = pStateListF "slider13" name xs slider13Count :: String -> ControlPattern slider13Count name = pStateF "slider13" name (maybe 0 (+1)) slider13CountTo :: String -> Pattern Double -> Pattern ValueMap slider13CountTo name ipat = innerJoin $ (\i -> pStateF "slider13" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat slider13bus :: Pattern Int -> Pattern Double -> ControlPattern slider13bus busid pat = (pF "slider13" pat) # (pI "^slider13" busid) slider13recv :: Pattern Int -> ControlPattern slider13recv busid = pI "^slider13" busid -- | slider14 :: Pattern Double -> ControlPattern slider14 = pF "slider14" slider14Take :: String -> [Double] -> ControlPattern slider14Take name xs = pStateListF "slider14" name xs slider14Count :: String -> ControlPattern slider14Count name = pStateF "slider14" name (maybe 0 (+1)) slider14CountTo :: String -> Pattern Double -> Pattern ValueMap slider14CountTo name ipat = innerJoin $ (\i -> pStateF "slider14" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat slider14bus :: Pattern Int -> Pattern Double -> ControlPattern slider14bus busid pat = (pF "slider14" pat) # (pI "^slider14" busid) slider14recv :: Pattern Int -> ControlPattern slider14recv busid = pI "^slider14" busid -- | slider15 :: Pattern Double -> ControlPattern slider15 = pF "slider15" slider15Take :: String -> [Double] -> ControlPattern slider15Take name xs = pStateListF "slider15" name xs slider15Count :: String -> ControlPattern slider15Count name = pStateF "slider15" name (maybe 0 (+1)) slider15CountTo :: String -> Pattern Double -> Pattern ValueMap slider15CountTo name ipat = innerJoin $ (\i -> pStateF "slider15" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat slider15bus :: Pattern Int -> Pattern Double -> ControlPattern slider15bus busid pat = (pF "slider15" pat) # (pI "^slider15" busid) slider15recv :: Pattern Int -> ControlPattern slider15recv busid = pI "^slider15" busid -- | slider2 :: Pattern Double -> ControlPattern slider2 = pF "slider2" slider2Take :: String -> [Double] -> ControlPattern slider2Take name xs = pStateListF "slider2" name xs slider2Count :: String -> ControlPattern slider2Count name = pStateF "slider2" name (maybe 0 (+1)) slider2CountTo :: String -> Pattern Double -> Pattern ValueMap slider2CountTo name ipat = innerJoin $ (\i -> pStateF "slider2" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat slider2bus :: Pattern Int -> Pattern Double -> ControlPattern slider2bus busid pat = (pF "slider2" pat) # (pI "^slider2" busid) slider2recv :: Pattern Int -> ControlPattern slider2recv busid = pI "^slider2" busid -- | slider3 :: Pattern Double -> ControlPattern slider3 = pF "slider3" slider3Take :: String -> [Double] -> ControlPattern slider3Take name xs = pStateListF "slider3" name xs slider3Count :: String -> ControlPattern slider3Count name = pStateF "slider3" name (maybe 0 (+1)) slider3CountTo :: String -> Pattern Double -> Pattern ValueMap slider3CountTo name ipat = innerJoin $ (\i -> pStateF "slider3" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat slider3bus :: Pattern Int -> Pattern Double -> ControlPattern slider3bus busid pat = (pF "slider3" pat) # (pI "^slider3" busid) slider3recv :: Pattern Int -> ControlPattern slider3recv busid = pI "^slider3" busid -- | slider4 :: Pattern Double -> ControlPattern slider4 = pF "slider4" slider4Take :: String -> [Double] -> ControlPattern slider4Take name xs = pStateListF "slider4" name xs slider4Count :: String -> ControlPattern slider4Count name = pStateF "slider4" name (maybe 0 (+1)) slider4CountTo :: String -> Pattern Double -> Pattern ValueMap slider4CountTo name ipat = innerJoin $ (\i -> pStateF "slider4" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat slider4bus :: Pattern Int -> Pattern Double -> ControlPattern slider4bus busid pat = (pF "slider4" pat) # (pI "^slider4" busid) slider4recv :: Pattern Int -> ControlPattern slider4recv busid = pI "^slider4" busid -- | slider5 :: Pattern Double -> ControlPattern slider5 = pF "slider5" slider5Take :: String -> [Double] -> ControlPattern slider5Take name xs = pStateListF "slider5" name xs slider5Count :: String -> ControlPattern slider5Count name = pStateF "slider5" name (maybe 0 (+1)) slider5CountTo :: String -> Pattern Double -> Pattern ValueMap slider5CountTo name ipat = innerJoin $ (\i -> pStateF "slider5" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat slider5bus :: Pattern Int -> Pattern Double -> ControlPattern slider5bus busid pat = (pF "slider5" pat) # (pI "^slider5" busid) slider5recv :: Pattern Int -> ControlPattern slider5recv busid = pI "^slider5" busid -- | slider6 :: Pattern Double -> ControlPattern slider6 = pF "slider6" slider6Take :: String -> [Double] -> ControlPattern slider6Take name xs = pStateListF "slider6" name xs slider6Count :: String -> ControlPattern slider6Count name = pStateF "slider6" name (maybe 0 (+1)) slider6CountTo :: String -> Pattern Double -> Pattern ValueMap slider6CountTo name ipat = innerJoin $ (\i -> pStateF "slider6" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat slider6bus :: Pattern Int -> Pattern Double -> ControlPattern slider6bus busid pat = (pF "slider6" pat) # (pI "^slider6" busid) slider6recv :: Pattern Int -> ControlPattern slider6recv busid = pI "^slider6" busid -- | slider7 :: Pattern Double -> ControlPattern slider7 = pF "slider7" slider7Take :: String -> [Double] -> ControlPattern slider7Take name xs = pStateListF "slider7" name xs slider7Count :: String -> ControlPattern slider7Count name = pStateF "slider7" name (maybe 0 (+1)) slider7CountTo :: String -> Pattern Double -> Pattern ValueMap slider7CountTo name ipat = innerJoin $ (\i -> pStateF "slider7" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat slider7bus :: Pattern Int -> Pattern Double -> ControlPattern slider7bus busid pat = (pF "slider7" pat) # (pI "^slider7" busid) slider7recv :: Pattern Int -> ControlPattern slider7recv busid = pI "^slider7" busid -- | slider8 :: Pattern Double -> ControlPattern slider8 = pF "slider8" slider8Take :: String -> [Double] -> ControlPattern slider8Take name xs = pStateListF "slider8" name xs slider8Count :: String -> ControlPattern slider8Count name = pStateF "slider8" name (maybe 0 (+1)) slider8CountTo :: String -> Pattern Double -> Pattern ValueMap slider8CountTo name ipat = innerJoin $ (\i -> pStateF "slider8" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat slider8bus :: Pattern Int -> Pattern Double -> ControlPattern slider8bus busid pat = (pF "slider8" pat) # (pI "^slider8" busid) slider8recv :: Pattern Int -> ControlPattern slider8recv busid = pI "^slider8" busid -- | slider9 :: Pattern Double -> ControlPattern slider9 = pF "slider9" slider9Take :: String -> [Double] -> ControlPattern slider9Take name xs = pStateListF "slider9" name xs slider9Count :: String -> ControlPattern slider9Count name = pStateF "slider9" name (maybe 0 (+1)) slider9CountTo :: String -> Pattern Double -> Pattern ValueMap slider9CountTo name ipat = innerJoin $ (\i -> pStateF "slider9" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat slider9bus :: Pattern Int -> Pattern Double -> ControlPattern slider9bus busid pat = (pF "slider9" pat) # (pI "^slider9" busid) slider9recv :: Pattern Int -> ControlPattern slider9recv busid = pI "^slider9" busid -- | Spectral smear smear :: Pattern Double -> ControlPattern smear = pF "smear" smearTake :: String -> [Double] -> ControlPattern smearTake name xs = pStateListF "smear" name xs smearCount :: String -> ControlPattern smearCount name = pStateF "smear" name (maybe 0 (+1)) smearCountTo :: String -> Pattern Double -> Pattern ValueMap smearCountTo name ipat = innerJoin $ (\i -> pStateF "smear" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat smearbus :: Pattern Int -> Pattern Double -> ControlPattern smearbus busid pat = (pF "smear" pat) # (pI "^smear" busid) smearrecv :: Pattern Int -> ControlPattern smearrecv busid = pI "^smear" busid -- | songPtr :: Pattern Double -> ControlPattern songPtr = pF "songPtr" songPtrTake :: String -> [Double] -> ControlPattern songPtrTake name xs = pStateListF "songPtr" name xs songPtrCount :: String -> ControlPattern songPtrCount name = pStateF "songPtr" name (maybe 0 (+1)) songPtrCountTo :: String -> Pattern Double -> Pattern ValueMap songPtrCountTo name ipat = innerJoin $ (\i -> pStateF "songPtr" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat songPtrbus :: Pattern Int -> Pattern Double -> ControlPattern songPtrbus _ _ = error $ "Control parameter 'songPtr' can't be sent to a bus." -- | a pattern of numbers which changes the speed of sample playback, i.e. a cheap way of changing pitch. Negative values will play the sample backwards! speed :: Pattern Double -> ControlPattern speed = pF "speed" speedTake :: String -> [Double] -> ControlPattern speedTake name xs = pStateListF "speed" name xs speedCount :: String -> ControlPattern speedCount name = pStateF "speed" name (maybe 0 (+1)) speedCountTo :: String -> Pattern Double -> Pattern ValueMap speedCountTo name ipat = innerJoin $ (\i -> pStateF "speed" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat speedbus :: Pattern Int -> Pattern Double -> ControlPattern speedbus _ _ = error $ "Control parameter 'speed' can't be sent to a bus." -- | squiz :: Pattern Double -> ControlPattern squiz = pF "squiz" squizTake :: String -> [Double] -> ControlPattern squizTake name xs = pStateListF "squiz" name xs squizCount :: String -> ControlPattern squizCount name = pStateF "squiz" name (maybe 0 (+1)) squizCountTo :: String -> Pattern Double -> Pattern ValueMap squizCountTo name ipat = innerJoin $ (\i -> pStateF "squiz" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat squizbus :: Pattern Int -> Pattern Double -> ControlPattern squizbus busid pat = (pF "squiz" pat) # (pI "^squiz" busid) squizrecv :: Pattern Int -> ControlPattern squizrecv busid = pI "^squiz" busid -- | stepsPerOctave :: Pattern Double -> ControlPattern stepsPerOctave = pF "stepsPerOctave" stepsPerOctaveTake :: String -> [Double] -> ControlPattern stepsPerOctaveTake name xs = pStateListF "stepsPerOctave" name xs stepsPerOctaveCount :: String -> ControlPattern stepsPerOctaveCount name = pStateF "stepsPerOctave" name (maybe 0 (+1)) stepsPerOctaveCountTo :: String -> Pattern Double -> Pattern ValueMap stepsPerOctaveCountTo name ipat = innerJoin $ (\i -> pStateF "stepsPerOctave" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat stepsPerOctavebus :: Pattern Int -> Pattern Double -> ControlPattern stepsPerOctavebus busid pat = (pF "stepsPerOctave" pat) # (pI "^stepsPerOctave" busid) stepsPerOctaverecv :: Pattern Int -> ControlPattern stepsPerOctaverecv busid = pI "^stepsPerOctave" busid -- | stutterdepth :: Pattern Double -> ControlPattern stutterdepth = pF "stutterdepth" stutterdepthTake :: String -> [Double] -> ControlPattern stutterdepthTake name xs = pStateListF "stutterdepth" name xs stutterdepthCount :: String -> ControlPattern stutterdepthCount name = pStateF "stutterdepth" name (maybe 0 (+1)) stutterdepthCountTo :: String -> Pattern Double -> Pattern ValueMap stutterdepthCountTo name ipat = innerJoin $ (\i -> pStateF "stutterdepth" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat stutterdepthbus :: Pattern Int -> Pattern Double -> ControlPattern stutterdepthbus busid pat = (pF "stutterdepth" pat) # (pI "^stutterdepth" busid) stutterdepthrecv :: Pattern Int -> ControlPattern stutterdepthrecv busid = pI "^stutterdepth" busid -- | stuttertime :: Pattern Double -> ControlPattern stuttertime = pF "stuttertime" stuttertimeTake :: String -> [Double] -> ControlPattern stuttertimeTake name xs = pStateListF "stuttertime" name xs stuttertimeCount :: String -> ControlPattern stuttertimeCount name = pStateF "stuttertime" name (maybe 0 (+1)) stuttertimeCountTo :: String -> Pattern Double -> Pattern ValueMap stuttertimeCountTo name ipat = innerJoin $ (\i -> pStateF "stuttertime" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat stuttertimebus :: Pattern Int -> Pattern Double -> ControlPattern stuttertimebus busid pat = (pF "stuttertime" pat) # (pI "^stuttertime" busid) stuttertimerecv :: Pattern Int -> ControlPattern stuttertimerecv busid = pI "^stuttertime" busid -- | sustain :: Pattern Double -> ControlPattern sustain = pF "sustain" sustainTake :: String -> [Double] -> ControlPattern sustainTake name xs = pStateListF "sustain" name xs sustainCount :: String -> ControlPattern sustainCount name = pStateF "sustain" name (maybe 0 (+1)) sustainCountTo :: String -> Pattern Double -> Pattern ValueMap sustainCountTo name ipat = innerJoin $ (\i -> pStateF "sustain" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat sustainbus :: Pattern Int -> Pattern Double -> ControlPattern sustainbus _ _ = error $ "Control parameter 'sustain' can't be sent to a bus." -- | sustainpedal :: Pattern Double -> ControlPattern sustainpedal = pF "sustainpedal" sustainpedalTake :: String -> [Double] -> ControlPattern sustainpedalTake name xs = pStateListF "sustainpedal" name xs sustainpedalCount :: String -> ControlPattern sustainpedalCount name = pStateF "sustainpedal" name (maybe 0 (+1)) sustainpedalCountTo :: String -> Pattern Double -> Pattern ValueMap sustainpedalCountTo name ipat = innerJoin $ (\i -> pStateF "sustainpedal" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat sustainpedalbus :: Pattern Int -> Pattern Double -> ControlPattern sustainpedalbus busid pat = (pF "sustainpedal" pat) # (pI "^sustainpedal" busid) sustainpedalrecv :: Pattern Int -> ControlPattern sustainpedalrecv busid = pI "^sustainpedal" busid -- | time stretch amount timescale :: Pattern Double -> ControlPattern timescale = pF "timescale" timescaleTake :: String -> [Double] -> ControlPattern timescaleTake name xs = pStateListF "timescale" name xs timescaleCount :: String -> ControlPattern timescaleCount name = pStateF "timescale" name (maybe 0 (+1)) timescaleCountTo :: String -> Pattern Double -> Pattern ValueMap timescaleCountTo name ipat = innerJoin $ (\i -> pStateF "timescale" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat timescalebus :: Pattern Int -> Pattern Double -> ControlPattern timescalebus _ _ = error $ "Control parameter 'timescale' can't be sent to a bus." -- | time stretch window size timescalewin :: Pattern Double -> ControlPattern timescalewin = pF "timescalewin" timescalewinTake :: String -> [Double] -> ControlPattern timescalewinTake name xs = pStateListF "timescalewin" name xs timescalewinCount :: String -> ControlPattern timescalewinCount name = pStateF "timescalewin" name (maybe 0 (+1)) timescalewinCountTo :: String -> Pattern Double -> Pattern ValueMap timescalewinCountTo name ipat = innerJoin $ (\i -> pStateF "timescalewin" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat timescalewinbus :: Pattern Int -> Pattern Double -> ControlPattern timescalewinbus _ _ = error $ "Control parameter 'timescalewin' can't be sent to a bus." -- | for internal sound routing to :: Pattern Double -> ControlPattern to = pF "to" toTake :: String -> [Double] -> ControlPattern toTake name xs = pStateListF "to" name xs toCount :: String -> ControlPattern toCount name = pStateF "to" name (maybe 0 (+1)) toCountTo :: String -> Pattern Double -> Pattern ValueMap toCountTo name ipat = innerJoin $ (\i -> pStateF "to" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat tobus :: Pattern Int -> Pattern Double -> ControlPattern tobus busid pat = (pF "to" pat) # (pI "^to" busid) torecv :: Pattern Int -> ControlPattern torecv busid = pI "^to" busid -- | for internal sound routing toArg :: Pattern String -> ControlPattern toArg = pS "toArg" toArgTake :: String -> [Double] -> ControlPattern toArgTake name xs = pStateListF "toArg" name xs toArgbus :: Pattern Int -> Pattern String -> ControlPattern toArgbus busid pat = (pS "toArg" pat) # (pI "^toArg" busid) toArgrecv :: Pattern Int -> ControlPattern toArgrecv busid = pI "^toArg" busid -- | tomdecay :: Pattern Double -> ControlPattern tomdecay = pF "tomdecay" tomdecayTake :: String -> [Double] -> ControlPattern tomdecayTake name xs = pStateListF "tomdecay" name xs tomdecayCount :: String -> ControlPattern tomdecayCount name = pStateF "tomdecay" name (maybe 0 (+1)) tomdecayCountTo :: String -> Pattern Double -> Pattern ValueMap tomdecayCountTo name ipat = innerJoin $ (\i -> pStateF "tomdecay" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat tomdecaybus :: Pattern Int -> Pattern Double -> ControlPattern tomdecaybus busid pat = (pF "tomdecay" pat) # (pI "^tomdecay" busid) tomdecayrecv :: Pattern Int -> ControlPattern tomdecayrecv busid = pI "^tomdecay" busid -- | Tremolo Audio DSP effect | params are 'tremolorate' and 'tremolodepth' tremolodepth :: Pattern Double -> ControlPattern tremolodepth = pF "tremolodepth" tremolodepthTake :: String -> [Double] -> ControlPattern tremolodepthTake name xs = pStateListF "tremolodepth" name xs tremolodepthCount :: String -> ControlPattern tremolodepthCount name = pStateF "tremolodepth" name (maybe 0 (+1)) tremolodepthCountTo :: String -> Pattern Double -> Pattern ValueMap tremolodepthCountTo name ipat = innerJoin $ (\i -> pStateF "tremolodepth" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat tremolodepthbus :: Pattern Int -> Pattern Double -> ControlPattern tremolodepthbus busid pat = (pF "tremolodepth" pat) # (pI "^tremolodepth" busid) tremolodepthrecv :: Pattern Int -> ControlPattern tremolodepthrecv busid = pI "^tremolodepth" busid -- | Tremolo Audio DSP effect | params are 'tremolorate' and 'tremolodepth' tremolorate :: Pattern Double -> ControlPattern tremolorate = pF "tremolorate" tremolorateTake :: String -> [Double] -> ControlPattern tremolorateTake name xs = pStateListF "tremolorate" name xs tremolorateCount :: String -> ControlPattern tremolorateCount name = pStateF "tremolorate" name (maybe 0 (+1)) tremolorateCountTo :: String -> Pattern Double -> Pattern ValueMap tremolorateCountTo name ipat = innerJoin $ (\i -> pStateF "tremolorate" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat tremoloratebus :: Pattern Int -> Pattern Double -> ControlPattern tremoloratebus busid pat = (pF "tremolorate" pat) # (pI "^tremolorate" busid) tremoloraterecv :: Pattern Int -> ControlPattern tremoloraterecv busid = pI "^tremolorate" busid -- | tube distortion triode :: Pattern Double -> ControlPattern triode = pF "triode" triodeTake :: String -> [Double] -> ControlPattern triodeTake name xs = pStateListF "triode" name xs triodeCount :: String -> ControlPattern triodeCount name = pStateF "triode" name (maybe 0 (+1)) triodeCountTo :: String -> Pattern Double -> Pattern ValueMap triodeCountTo name ipat = innerJoin $ (\i -> pStateF "triode" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat triodebus :: Pattern Int -> Pattern Double -> ControlPattern triodebus busid pat = (pF "triode" pat) # (pI "^triode" busid) trioderecv :: Pattern Int -> ControlPattern trioderecv busid = pI "^triode" busid -- | tsdelay :: Pattern Double -> ControlPattern tsdelay = pF "tsdelay" tsdelayTake :: String -> [Double] -> ControlPattern tsdelayTake name xs = pStateListF "tsdelay" name xs tsdelayCount :: String -> ControlPattern tsdelayCount name = pStateF "tsdelay" name (maybe 0 (+1)) tsdelayCountTo :: String -> Pattern Double -> Pattern ValueMap tsdelayCountTo name ipat = innerJoin $ (\i -> pStateF "tsdelay" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat tsdelaybus :: Pattern Int -> Pattern Double -> ControlPattern tsdelaybus busid pat = (pF "tsdelay" pat) # (pI "^tsdelay" busid) tsdelayrecv :: Pattern Int -> ControlPattern tsdelayrecv busid = pI "^tsdelay" busid -- | uid :: Pattern Double -> ControlPattern uid = pF "uid" uidTake :: String -> [Double] -> ControlPattern uidTake name xs = pStateListF "uid" name xs uidCount :: String -> ControlPattern uidCount name = pStateF "uid" name (maybe 0 (+1)) uidCountTo :: String -> Pattern Double -> Pattern ValueMap uidCountTo name ipat = innerJoin $ (\i -> pStateF "uid" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat uidbus :: Pattern Int -> Pattern Double -> ControlPattern uidbus _ _ = error $ "Control parameter 'uid' can't be sent to a bus." -- | used in conjunction with `speed`, accepts values of "r" (rate, default behavior), "c" (cycles), or "s" (seconds). Using `unit "c"` means `speed` will be interpreted in units of cycles, e.g. `speed "1"` means samples will be stretched to fill a cycle. Using `unit "s"` means the playback speed will be adjusted so that the duration is the number of seconds specified by `speed`. unit :: Pattern String -> ControlPattern unit = pS "unit" unitTake :: String -> [Double] -> ControlPattern unitTake name xs = pStateListF "unit" name xs unitbus :: Pattern Int -> Pattern String -> ControlPattern unitbus _ _ = error $ "Control parameter 'unit' can't be sent to a bus." -- | val :: Pattern Double -> ControlPattern val = pF "val" valTake :: String -> [Double] -> ControlPattern valTake name xs = pStateListF "val" name xs valCount :: String -> ControlPattern valCount name = pStateF "val" name (maybe 0 (+1)) valCountTo :: String -> Pattern Double -> Pattern ValueMap valCountTo name ipat = innerJoin $ (\i -> pStateF "val" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat valbus :: Pattern Int -> Pattern Double -> ControlPattern valbus _ _ = error $ "Control parameter 'val' can't be sent to a bus." -- | vcfegint :: Pattern Double -> ControlPattern vcfegint = pF "vcfegint" vcfegintTake :: String -> [Double] -> ControlPattern vcfegintTake name xs = pStateListF "vcfegint" name xs vcfegintCount :: String -> ControlPattern vcfegintCount name = pStateF "vcfegint" name (maybe 0 (+1)) vcfegintCountTo :: String -> Pattern Double -> Pattern ValueMap vcfegintCountTo name ipat = innerJoin $ (\i -> pStateF "vcfegint" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat vcfegintbus :: Pattern Int -> Pattern Double -> ControlPattern vcfegintbus busid pat = (pF "vcfegint" pat) # (pI "^vcfegint" busid) vcfegintrecv :: Pattern Int -> ControlPattern vcfegintrecv busid = pI "^vcfegint" busid -- | vcoegint :: Pattern Double -> ControlPattern vcoegint = pF "vcoegint" vcoegintTake :: String -> [Double] -> ControlPattern vcoegintTake name xs = pStateListF "vcoegint" name xs vcoegintCount :: String -> ControlPattern vcoegintCount name = pStateF "vcoegint" name (maybe 0 (+1)) vcoegintCountTo :: String -> Pattern Double -> Pattern ValueMap vcoegintCountTo name ipat = innerJoin $ (\i -> pStateF "vcoegint" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat vcoegintbus :: Pattern Int -> Pattern Double -> ControlPattern vcoegintbus busid pat = (pF "vcoegint" pat) # (pI "^vcoegint" busid) vcoegintrecv :: Pattern Int -> ControlPattern vcoegintrecv busid = pI "^vcoegint" busid -- | velocity :: Pattern Double -> ControlPattern velocity = pF "velocity" velocityTake :: String -> [Double] -> ControlPattern velocityTake name xs = pStateListF "velocity" name xs velocityCount :: String -> ControlPattern velocityCount name = pStateF "velocity" name (maybe 0 (+1)) velocityCountTo :: String -> Pattern Double -> Pattern ValueMap velocityCountTo name ipat = innerJoin $ (\i -> pStateF "velocity" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat velocitybus :: Pattern Int -> Pattern Double -> ControlPattern velocitybus busid pat = (pF "velocity" pat) # (pI "^velocity" busid) velocityrecv :: Pattern Int -> ControlPattern velocityrecv busid = pI "^velocity" busid -- | voice :: Pattern Double -> ControlPattern voice = pF "voice" voiceTake :: String -> [Double] -> ControlPattern voiceTake name xs = pStateListF "voice" name xs voiceCount :: String -> ControlPattern voiceCount name = pStateF "voice" name (maybe 0 (+1)) voiceCountTo :: String -> Pattern Double -> Pattern ValueMap voiceCountTo name ipat = innerJoin $ (\i -> pStateF "voice" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat voicebus :: Pattern Int -> Pattern Double -> ControlPattern voicebus busid pat = (pF "voice" pat) # (pI "^voice" busid) voicerecv :: Pattern Int -> ControlPattern voicerecv busid = pI "^voice" busid -- | formant filter to make things sound like vowels, a pattern of either `a`, `e`, `i`, `o` or `u`. Use a rest (`~`) for no effect. vowel :: Pattern String -> ControlPattern vowel = pS "vowel" vowelTake :: String -> [Double] -> ControlPattern vowelTake name xs = pStateListF "vowel" name xs vowelbus :: Pattern Int -> Pattern String -> ControlPattern vowelbus busid pat = (pS "vowel" pat) # (pI "^vowel" busid) vowelrecv :: Pattern Int -> ControlPattern vowelrecv busid = pI "^vowel" busid -- | waveloss :: Pattern Double -> ControlPattern waveloss = pF "waveloss" wavelossTake :: String -> [Double] -> ControlPattern wavelossTake name xs = pStateListF "waveloss" name xs wavelossCount :: String -> ControlPattern wavelossCount name = pStateF "waveloss" name (maybe 0 (+1)) wavelossCountTo :: String -> Pattern Double -> Pattern ValueMap wavelossCountTo name ipat = innerJoin $ (\i -> pStateF "waveloss" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat wavelossbus :: Pattern Int -> Pattern Double -> ControlPattern wavelossbus busid pat = (pF "waveloss" pat) # (pI "^waveloss" busid) wavelossrecv :: Pattern Int -> ControlPattern wavelossrecv busid = pI "^waveloss" busid -- | xsdelay :: Pattern Double -> ControlPattern xsdelay = pF "xsdelay" xsdelayTake :: String -> [Double] -> ControlPattern xsdelayTake name xs = pStateListF "xsdelay" name xs xsdelayCount :: String -> ControlPattern xsdelayCount name = pStateF "xsdelay" name (maybe 0 (+1)) xsdelayCountTo :: String -> Pattern Double -> Pattern ValueMap xsdelayCountTo name ipat = innerJoin $ (\i -> pStateF "xsdelay" name (maybe 0 ((`mod'` i) . (+1)))) <$> ipat xsdelaybus :: Pattern Int -> Pattern Double -> ControlPattern xsdelaybus busid pat = (pF "xsdelay" pat) # (pI "^xsdelay" busid) xsdelayrecv :: Pattern Int -> ControlPattern xsdelayrecv busid = pI "^xsdelay" busid -- aliases voi :: Pattern Double -> ControlPattern voi = voice voibus :: Pattern Int -> Pattern Double -> ControlPattern voibus = voicebus voirecv :: Pattern Int -> ControlPattern voirecv = voicerecv vco :: Pattern Double -> ControlPattern vco = vcoegint vcobus :: Pattern Int -> Pattern Double -> ControlPattern vcobus = vcoegintbus vcorecv :: Pattern Int -> ControlPattern vcorecv = vcoegintrecv vcf :: Pattern Double -> ControlPattern vcf = vcfegint vcfbus :: Pattern Int -> Pattern Double -> ControlPattern vcfbus = vcfegintbus vcfrecv :: Pattern Int -> ControlPattern vcfrecv = vcfegintrecv up :: Pattern Note -> ControlPattern up = note tremr :: Pattern Double -> ControlPattern tremr = tremolorate tremrbus :: Pattern Int -> Pattern Double -> ControlPattern tremrbus = tremoloratebus tremrrecv :: Pattern Int -> ControlPattern tremrrecv = tremoloraterecv tremdp :: Pattern Double -> ControlPattern tremdp = tremolodepth tremdpbus :: Pattern Int -> Pattern Double -> ControlPattern tremdpbus = tremolodepthbus tremdprecv :: Pattern Int -> ControlPattern tremdprecv = tremolodepthrecv tdecay :: Pattern Double -> ControlPattern tdecay = tomdecay tdecaybus :: Pattern Int -> Pattern Double -> ControlPattern tdecaybus = tomdecaybus tdecayrecv :: Pattern Int -> ControlPattern tdecayrecv = tomdecayrecv sz :: Pattern Double -> ControlPattern sz = size szbus :: Pattern Int -> Pattern Double -> ControlPattern szbus = sizebus szrecv :: Pattern Int -> ControlPattern szrecv = sizerecv sus :: Pattern Double -> ControlPattern sus = sustain stt :: Pattern Double -> ControlPattern stt = stuttertime sttbus :: Pattern Int -> Pattern Double -> ControlPattern sttbus = stuttertimebus sttrecv :: Pattern Int -> ControlPattern sttrecv = stuttertimerecv std :: Pattern Double -> ControlPattern std = stutterdepth stdbus :: Pattern Int -> Pattern Double -> ControlPattern stdbus = stutterdepthbus stdrecv :: Pattern Int -> ControlPattern stdrecv = stutterdepthrecv sld :: Pattern Double -> ControlPattern sld = slide sldbus :: Pattern Int -> Pattern Double -> ControlPattern sldbus = slidebus sldrecv :: Pattern Int -> ControlPattern sldrecv = sliderecv scr :: Pattern Double -> ControlPattern scr = scrash scrbus :: Pattern Int -> Pattern Double -> ControlPattern scrbus = scrashbus scrrecv :: Pattern Int -> ControlPattern scrrecv = scrashrecv scp :: Pattern Double -> ControlPattern scp = sclap scpbus :: Pattern Int -> Pattern Double -> ControlPattern scpbus = sclapbus scprecv :: Pattern Int -> ControlPattern scprecv = sclaprecv scl :: Pattern Double -> ControlPattern scl = sclaves sclbus :: Pattern Int -> Pattern Double -> ControlPattern sclbus = sclavesbus sclrecv :: Pattern Int -> ControlPattern sclrecv = sclavesrecv sag :: Pattern Double -> ControlPattern sag = sagogo sagbus :: Pattern Int -> Pattern Double -> ControlPattern sagbus = sagogobus sagrecv :: Pattern Int -> ControlPattern sagrecv = sagogorecv s :: Pattern String -> ControlPattern s = sound rel :: Pattern Double -> ControlPattern rel = release relbus :: Pattern Int -> Pattern Double -> ControlPattern relbus = releasebus relrecv :: Pattern Int -> ControlPattern relrecv = releaserecv por :: Pattern Double -> ControlPattern por = portamento porbus :: Pattern Int -> Pattern Double -> ControlPattern porbus = portamentobus porrecv :: Pattern Int -> ControlPattern porrecv = portamentorecv pit3 :: Pattern Double -> ControlPattern pit3 = pitch3 pit3bus :: Pattern Int -> Pattern Double -> ControlPattern pit3bus = pitch3bus pit3recv :: Pattern Int -> ControlPattern pit3recv = pitch3recv pit2 :: Pattern Double -> ControlPattern pit2 = pitch2 pit2bus :: Pattern Int -> Pattern Double -> ControlPattern pit2bus = pitch2bus pit2recv :: Pattern Int -> ControlPattern pit2recv = pitch2recv pit1 :: Pattern Double -> ControlPattern pit1 = pitch1 pit1bus :: Pattern Int -> Pattern Double -> ControlPattern pit1bus = pitch1bus pit1recv :: Pattern Int -> ControlPattern pit1recv = pitch1recv phasr :: Pattern Double -> ControlPattern phasr = phaserrate phasrbus :: Pattern Int -> Pattern Double -> ControlPattern phasrbus = phaserratebus phasrrecv :: Pattern Int -> ControlPattern phasrrecv = phaserraterecv phasdp :: Pattern Double -> ControlPattern phasdp = phaserdepth phasdpbus :: Pattern Int -> Pattern Double -> ControlPattern phasdpbus = phaserdepthbus phasdprecv :: Pattern Int -> ControlPattern phasdprecv = phaserdepthrecv ohdecay :: Pattern Double -> ControlPattern ohdecay = ophatdecay ohdecaybus :: Pattern Int -> Pattern Double -> ControlPattern ohdecaybus = ophatdecaybus ohdecayrecv :: Pattern Int -> ControlPattern ohdecayrecv = ophatdecayrecv number :: Pattern Note -> ControlPattern number = n lsn :: Pattern Double -> ControlPattern lsn = lsnare lsnbus :: Pattern Int -> Pattern Double -> ControlPattern lsnbus = lsnarebus lsnrecv :: Pattern Int -> ControlPattern lsnrecv = lsnarerecv lpq :: Pattern Double -> ControlPattern lpq = resonance lpqbus :: Pattern Int -> Pattern Double -> ControlPattern lpqbus = resonancebus lpqrecv :: Pattern Int -> ControlPattern lpqrecv = resonancerecv lpf :: Pattern Double -> ControlPattern lpf = cutoff lpfbus :: Pattern Int -> Pattern Double -> ControlPattern lpfbus = cutoffbus lpfrecv :: Pattern Int -> ControlPattern lpfrecv = cutoffrecv loh :: Pattern Double -> ControlPattern loh = lophat lohbus :: Pattern Int -> Pattern Double -> ControlPattern lohbus = lophatbus lohrecv :: Pattern Int -> ControlPattern lohrecv = lophatrecv llt :: Pattern Double -> ControlPattern llt = llotom lltbus :: Pattern Int -> Pattern Double -> ControlPattern lltbus = llotombus lltrecv :: Pattern Int -> ControlPattern lltrecv = llotomrecv lht :: Pattern Double -> ControlPattern lht = lhitom lhtbus :: Pattern Int -> Pattern Double -> ControlPattern lhtbus = lhitombus lhtrecv :: Pattern Int -> ControlPattern lhtrecv = lhitomrecv lfop :: Pattern Double -> ControlPattern lfop = lfopitchint lfopbus :: Pattern Int -> Pattern Double -> ControlPattern lfopbus = lfopitchintbus lfoprecv :: Pattern Int -> ControlPattern lfoprecv = lfopitchintrecv lfoi :: Pattern Double -> ControlPattern lfoi = lfoint lfoibus :: Pattern Int -> Pattern Double -> ControlPattern lfoibus = lfointbus lfoirecv :: Pattern Int -> ControlPattern lfoirecv = lfointrecv lfoc :: Pattern Double -> ControlPattern lfoc = lfocutoffint lfocbus :: Pattern Int -> Pattern Double -> ControlPattern lfocbus = lfocutoffintbus lfocrecv :: Pattern Int -> ControlPattern lfocrecv = lfocutoffintrecv lcr :: Pattern Double -> ControlPattern lcr = lcrash lcrbus :: Pattern Int -> Pattern Double -> ControlPattern lcrbus = lcrashbus lcrrecv :: Pattern Int -> ControlPattern lcrrecv = lcrashrecv lcp :: Pattern Double -> ControlPattern lcp = lclap lcpbus :: Pattern Int -> Pattern Double -> ControlPattern lcpbus = lclapbus lcprecv :: Pattern Int -> ControlPattern lcprecv = lclaprecv lcl :: Pattern Double -> ControlPattern lcl = lclaves lclbus :: Pattern Int -> Pattern Double -> ControlPattern lclbus = lclavesbus lclrecv :: Pattern Int -> ControlPattern lclrecv = lclavesrecv lch :: Pattern Double -> ControlPattern lch = lclhat lchbus :: Pattern Int -> Pattern Double -> ControlPattern lchbus = lclhatbus lchrecv :: Pattern Int -> ControlPattern lchrecv = lclhatrecv lbd :: Pattern Double -> ControlPattern lbd = lkick lbdbus :: Pattern Int -> Pattern Double -> ControlPattern lbdbus = lkickbus lbdrecv :: Pattern Int -> ControlPattern lbdrecv = lkickrecv lag :: Pattern Double -> ControlPattern lag = lagogo lagbus :: Pattern Int -> Pattern Double -> ControlPattern lagbus = lagogobus lagrecv :: Pattern Int -> ControlPattern lagrecv = lagogorecv hpq :: Pattern Double -> ControlPattern hpq = hresonance hpqbus :: Pattern Int -> Pattern Double -> ControlPattern hpqbus = hresonancebus hpqrecv :: Pattern Int -> ControlPattern hpqrecv = hresonancerecv hpf :: Pattern Double -> ControlPattern hpf = hcutoff hpfbus :: Pattern Int -> Pattern Double -> ControlPattern hpfbus = hcutoffbus hpfrecv :: Pattern Int -> ControlPattern hpfrecv = hcutoffrecv hg :: Pattern Double -> ControlPattern hg = hatgrain hgbus :: Pattern Int -> Pattern Double -> ControlPattern hgbus = hatgrainbus hgrecv :: Pattern Int -> ControlPattern hgrecv = hatgrainrecv gat :: Pattern Double -> ControlPattern gat = gate gatbus :: Pattern Int -> Pattern Double -> ControlPattern gatbus = gatebus gatrecv :: Pattern Int -> ControlPattern gatrecv = gaterecv fadeOutTime :: Pattern Double -> ControlPattern fadeOutTime = fadeTime dt :: Pattern Double -> ControlPattern dt = delaytime dtbus :: Pattern Int -> Pattern Double -> ControlPattern dtbus = delaytimebus dtrecv :: Pattern Int -> ControlPattern dtrecv = delaytimerecv dfb :: Pattern Double -> ControlPattern dfb = delayfeedback dfbbus :: Pattern Int -> Pattern Double -> ControlPattern dfbbus = delayfeedbackbus dfbrecv :: Pattern Int -> ControlPattern dfbrecv = delayfeedbackrecv det :: Pattern Double -> ControlPattern det = detune detbus :: Pattern Int -> Pattern Double -> ControlPattern detbus = detunebus detrecv :: Pattern Int -> ControlPattern detrecv = detunerecv delayt :: Pattern Double -> ControlPattern delayt = delaytime delaytbus :: Pattern Int -> Pattern Double -> ControlPattern delaytbus = delaytimebus delaytrecv :: Pattern Int -> ControlPattern delaytrecv = delaytimerecv delayfb :: Pattern Double -> ControlPattern delayfb = delayfeedback delayfbbus :: Pattern Int -> Pattern Double -> ControlPattern delayfbbus = delayfeedbackbus delayfbrecv :: Pattern Int -> ControlPattern delayfbrecv = delayfeedbackrecv ctfg :: Pattern Double -> ControlPattern ctfg = cutoffegint ctfgbus :: Pattern Int -> Pattern Double -> ControlPattern ctfgbus = cutoffegintbus ctfgrecv :: Pattern Int -> ControlPattern ctfgrecv = cutoffegintrecv ctf :: Pattern Double -> ControlPattern ctf = cutoff ctfbus :: Pattern Int -> Pattern Double -> ControlPattern ctfbus = cutoffbus ctfrecv :: Pattern Int -> ControlPattern ctfrecv = cutoffrecv chdecay :: Pattern Double -> ControlPattern chdecay = clhatdecay chdecaybus :: Pattern Int -> Pattern Double -> ControlPattern chdecaybus = clhatdecaybus chdecayrecv :: Pattern Int -> ControlPattern chdecayrecv = clhatdecayrecv bpq :: Pattern Double -> ControlPattern bpq = bandq bpqbus :: Pattern Int -> Pattern Double -> ControlPattern bpqbus = bandqbus bpqrecv :: Pattern Int -> ControlPattern bpqrecv = bandqrecv bpf :: Pattern Double -> ControlPattern bpf = bandf bpfbus :: Pattern Int -> Pattern Double -> ControlPattern bpfbus = bandfbus bpfrecv :: Pattern Int -> ControlPattern bpfrecv = bandfrecv att :: Pattern Double -> ControlPattern att = attack attbus :: Pattern Int -> Pattern Double -> ControlPattern attbus = attackbus attrecv :: Pattern Int -> ControlPattern attrecv = attackrecv