module Synth.Shared.Control where
import qualified Data.Map as Map
import qualified Data.String as String
import qualified Util.Num as Num
import qualified Util.Serialize as Serialize
import Global
newtype Control = Control Text
deriving (Control -> Control -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Control -> Control -> Bool
$c/= :: Control -> Control -> Bool
== :: Control -> Control -> Bool
$c== :: Control -> Control -> Bool
Eq, Eq Control
Control -> Control -> Bool
Control -> Control -> Ordering
Control -> Control -> Control
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Control -> Control -> Control
$cmin :: Control -> Control -> Control
max :: Control -> Control -> Control
$cmax :: Control -> Control -> Control
>= :: Control -> Control -> Bool
$c>= :: Control -> Control -> Bool
> :: Control -> Control -> Bool
$c> :: Control -> Control -> Bool
<= :: Control -> Control -> Bool
$c<= :: Control -> Control -> Bool
< :: Control -> Control -> Bool
$c< :: Control -> Control -> Bool
compare :: Control -> Control -> Ordering
$ccompare :: Control -> Control -> Ordering
Ord, Int -> Control -> ShowS
[Control] -> ShowS
Control -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Control] -> ShowS
$cshowList :: [Control] -> ShowS
show :: Control -> String
$cshow :: Control -> String
showsPrec :: Int -> Control -> ShowS
$cshowsPrec :: Int -> Control -> ShowS
Show, String -> Control
forall a. (String -> a) -> IsString a
fromString :: String -> Control
$cfromString :: String -> Control
String.IsString, Get Control
Putter Control
forall a. Putter a -> Get a -> Serialize a
get :: Get Control
$cget :: Get Control
put :: Putter Control
$cput :: Putter Control
Serialize.Serialize)
instance Pretty Control where pretty :: Control -> Text
pretty (Control Text
c) = Text
c
dynamic :: Control
dynamic :: Control
dynamic = Control
"dyn"
volume :: Control
volume :: Control
volume = Control
"vol"
minimumDb :: Double
minimumDb :: Double
minimumDb = -Double
96
dbToVolume :: Double -> Double
dbToVolume :: Double -> Double
dbToVolume = forall a. (Eq a, Fractional a) => a -> a -> a -> a
Num.normalize Double
minimumDb Double
0
pan :: Control
pan :: Control
pan = Control
"pan"
pitch :: Control
pitch :: Control
pitch = Control
"pitch"
gate :: Control
gate :: Control
gate = Control
"gate"
variation :: Control
variation :: Control
variation = Control
"variation"
mute :: Control
mute :: Control
mute = Control
"mute"
sampleStartOffset :: Control
sampleStartOffset :: Control
sampleStartOffset = Control
"sample-start-offset"
supportSampleStartOffset :: Supported
supportSampleStartOffset :: Supported
supportSampleStartOffset = Control -> Text -> Supported
support
Control
sampleStartOffset Text
"Sample start offset, in frames."
sampleTimeStretch :: Control
sampleTimeStretch :: Control
sampleTimeStretch = Control
"sample-time-stretch"
supportSampleTimeStretch :: Supported
supportSampleTimeStretch :: Supported
supportSampleTimeStretch = Control -> Text -> Supported
support
Control
sampleTimeStretch Text
"Time stretch ratio."
samplePitchShift :: Control
samplePitchShift :: Control
samplePitchShift = Control
"sample-pitch-shift"
supportSamplePitchShift :: Supported
supportSamplePitchShift :: Supported
supportSamplePitchShift = Control -> Text -> Supported
support
Control
samplePitchShift Text
"Pitch shift, in nn."
type Supported = Map Control Text
support :: Control -> Text -> Supported
support :: Control -> Text -> Supported
support = forall k a. k -> a -> Map k a
Map.singleton
supportPitch :: Supported
supportPitch :: Supported
supportPitch = Control -> Text -> Supported
support Control
pitch Text
"Pitch signal."
supportDyn :: Supported
supportDyn :: Supported
supportDyn = Control -> Text -> Supported
support Control
dynamic forall a b. (a -> b) -> a -> b
$
Text
"Dynamic signal. dB scale, where 0 is " forall a. Semigroup a => a -> a -> a
<> forall a. Pretty a => a -> Text
pretty Double
minimumDb forall a. Semigroup a => a -> a -> a
<> Text
" dB."
supportVariation :: Supported
supportVariation :: Supported
supportVariation = Control -> Text -> Supported
support
Control
variation Text
"Random integer, to choose between variant samples."