{-# Language CPP #-}
module Csound.Typed.GlobalState.Options (
Options(..),
defGain, defSampleRate, defBlockSize, defTabFi, defScaleUI,
TabFi(..), fineFi, coarseFi,
idWavs, idMp3s, idDoubles, idSines, idSines3, idSines2,
idPartials, idSines4, idBuzzes, idConsts, idLins, idCubes,
idExps, idSplines, idStartEnds, idPolys, idChebs1, idChebs2, idBessels, idWins,
idTabHarmonics, idMixOnTab, idMixTabs,
idNormTab, idPolynomFuns, idLinTab, idRandDists, idReadNumFile, idReadNumTab,
idExpsBreakPoints, idLinsBreakPoints, idReadTrajectoryFile, idMixSines1, idMixSines2,
idRandHist, idRandPairs, idRandRanges, idPvocex, idTuning, idMultichannel,
idPadsynth, idTanh, idExp, idSone, idFarey, idWave,
Jacko(..), JackoConnect, renderJacko,
csdNeedTrace
) where
import Control.Applicative
import Data.Default
import Data.Maybe
import qualified Data.IntMap as IM
import qualified Data.Map as M
import Csound.Dynamic hiding (csdFlags)
data Options = Options
{ Options -> Flags
csdFlags :: Flags
, Options -> Maybe Int
csdSampleRate :: Maybe Int
, Options -> Maybe Int
csdBlockSize :: Maybe Int
, Options -> Maybe Double
csdGain :: Maybe Double
, Options -> Maybe TabFi
csdTabFi :: Maybe TabFi
, Options -> Maybe (Double, Double)
csdScaleUI :: Maybe (Double, Double)
, Options -> Maybe Jacko
csdJacko :: Maybe Jacko
, Options -> Maybe [(String, String)]
csdJackConnect :: Maybe [(String, String)]
, Options -> Maybe Bool
csdTrace :: Maybe Bool
} deriving (Options -> Options -> Bool
(Options -> Options -> Bool)
-> (Options -> Options -> Bool) -> Eq Options
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Options -> Options -> Bool
$c/= :: Options -> Options -> Bool
== :: Options -> Options -> Bool
$c== :: Options -> Options -> Bool
Eq, Int -> Options -> ShowS
[Options] -> ShowS
Options -> String
(Int -> Options -> ShowS)
-> (Options -> String) -> ([Options] -> ShowS) -> Show Options
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Options] -> ShowS
$cshowList :: [Options] -> ShowS
show :: Options -> String
$cshow :: Options -> String
showsPrec :: Int -> Options -> ShowS
$cshowsPrec :: Int -> Options -> ShowS
Show, ReadPrec [Options]
ReadPrec Options
Int -> ReadS Options
ReadS [Options]
(Int -> ReadS Options)
-> ReadS [Options]
-> ReadPrec Options
-> ReadPrec [Options]
-> Read Options
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Options]
$creadListPrec :: ReadPrec [Options]
readPrec :: ReadPrec Options
$creadPrec :: ReadPrec Options
readList :: ReadS [Options]
$creadList :: ReadS [Options]
readsPrec :: Int -> ReadS Options
$creadsPrec :: Int -> ReadS Options
Read)
instance Default Options where
def :: Options
def = Flags
-> Maybe Int
-> Maybe Int
-> Maybe Double
-> Maybe TabFi
-> Maybe (Double, Double)
-> Maybe Jacko
-> Maybe [(String, String)]
-> Maybe Bool
-> Options
Options Flags
forall a. Default a => a
def Maybe Int
forall a. Default a => a
def Maybe Int
forall a. Default a => a
def Maybe Double
forall a. Default a => a
def Maybe TabFi
forall a. Default a => a
def Maybe (Double, Double)
forall a. Default a => a
def Maybe Jacko
forall a. Default a => a
def Maybe [(String, String)]
forall a. Default a => a
def Maybe Bool
forall a. Default a => a
def
#if MIN_VERSION_base(4,11,0)
instance Semigroup Options where
<> :: Options -> Options -> Options
(<>) = Options -> Options -> Options
mappendOptions
instance Monoid Options where
mempty :: Options
mempty = Options
forall a. Default a => a
def
#else
instance Monoid Options where
mempty = def
mappend = mappendOptions
#endif
mappendOptions :: Options -> Options -> Options
mappendOptions :: Options -> Options -> Options
mappendOptions Options
a Options
b = Options :: Flags
-> Maybe Int
-> Maybe Int
-> Maybe Double
-> Maybe TabFi
-> Maybe (Double, Double)
-> Maybe Jacko
-> Maybe [(String, String)]
-> Maybe Bool
-> Options
Options
{ csdFlags :: Flags
csdFlags = Flags -> Flags -> Flags
forall a. Monoid a => a -> a -> a
mappend (Options -> Flags
csdFlags Options
a) (Options -> Flags
csdFlags Options
b)
, csdSampleRate :: Maybe Int
csdSampleRate = Options -> Maybe Int
csdSampleRate Options
a Maybe Int -> Maybe Int -> Maybe Int
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Options -> Maybe Int
csdSampleRate Options
b
, csdBlockSize :: Maybe Int
csdBlockSize = Options -> Maybe Int
csdBlockSize Options
a Maybe Int -> Maybe Int -> Maybe Int
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Options -> Maybe Int
csdBlockSize Options
b
, csdGain :: Maybe Double
csdGain = Options -> Maybe Double
csdGain Options
a Maybe Double -> Maybe Double -> Maybe Double
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Options -> Maybe Double
csdGain Options
b
, csdTabFi :: Maybe TabFi
csdTabFi = Options -> Maybe TabFi
csdTabFi Options
a Maybe TabFi -> Maybe TabFi -> Maybe TabFi
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Options -> Maybe TabFi
csdTabFi Options
b
, csdScaleUI :: Maybe (Double, Double)
csdScaleUI = Options -> Maybe (Double, Double)
csdScaleUI Options
a Maybe (Double, Double)
-> Maybe (Double, Double) -> Maybe (Double, Double)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Options -> Maybe (Double, Double)
csdScaleUI Options
b
, csdJacko :: Maybe Jacko
csdJacko = Options -> Maybe Jacko
csdJacko Options
a Maybe Jacko -> Maybe Jacko -> Maybe Jacko
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Options -> Maybe Jacko
csdJacko Options
b
, csdJackConnect :: Maybe [(String, String)]
csdJackConnect = Options -> Maybe [(String, String)]
csdJackConnect Options
a Maybe [(String, String)]
-> Maybe [(String, String)] -> Maybe [(String, String)]
forall a. Semigroup a => a -> a -> a
<> Options -> Maybe [(String, String)]
csdJackConnect Options
b
, csdTrace :: Maybe Bool
csdTrace = Options -> Maybe Bool
csdTrace Options
a Maybe Bool -> Maybe Bool -> Maybe Bool
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Options -> Maybe Bool
csdTrace Options
b }
defScaleUI :: Options -> (Double, Double)
defScaleUI :: Options -> (Double, Double)
defScaleUI = (Double, Double)
-> ((Double, Double) -> (Double, Double))
-> Maybe (Double, Double)
-> (Double, Double)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Double
1, Double
1) (Double, Double) -> (Double, Double)
forall a. a -> a
id (Maybe (Double, Double) -> (Double, Double))
-> (Options -> Maybe (Double, Double))
-> Options
-> (Double, Double)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> Maybe (Double, Double)
csdScaleUI
defGain :: Options -> Double
defGain :: Options -> Double
defGain = Double -> (Double -> Double) -> Maybe Double -> Double
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Double
0.8 Double -> Double
forall a. a -> a
id (Maybe Double -> Double)
-> (Options -> Maybe Double) -> Options -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> Maybe Double
csdGain
defSampleRate :: Options -> Int
defSampleRate :: Options -> Int
defSampleRate = Int -> (Int -> Int) -> Maybe Int -> Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Int
44100 Int -> Int
forall a. a -> a
id (Maybe Int -> Int) -> (Options -> Maybe Int) -> Options -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> Maybe Int
csdSampleRate
defBlockSize :: Options -> Int
defBlockSize :: Options -> Int
defBlockSize = Int -> (Int -> Int) -> Maybe Int -> Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Int
64 Int -> Int
forall a. a -> a
id (Maybe Int -> Int) -> (Options -> Maybe Int) -> Options -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> Maybe Int
csdBlockSize
defTabFi :: Options -> TabFi
defTabFi :: Options -> TabFi
defTabFi = TabFi -> (TabFi -> TabFi) -> Maybe TabFi -> TabFi
forall b a. b -> (a -> b) -> Maybe a -> b
maybe TabFi
forall a. Default a => a
def TabFi -> TabFi
forall a. a -> a
id (Maybe TabFi -> TabFi)
-> (Options -> Maybe TabFi) -> Options -> TabFi
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Options -> Maybe TabFi
csdTabFi
data TabFi = TabFi
{ TabFi -> Int
tabFiBase :: Int
, TabFi -> IntMap Int
tabFiGens :: IM.IntMap Int
, TabFi -> Map String Int
tabNamedFiGens :: M.Map String Int
} deriving (TabFi -> TabFi -> Bool
(TabFi -> TabFi -> Bool) -> (TabFi -> TabFi -> Bool) -> Eq TabFi
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TabFi -> TabFi -> Bool
$c/= :: TabFi -> TabFi -> Bool
== :: TabFi -> TabFi -> Bool
$c== :: TabFi -> TabFi -> Bool
Eq, Int -> TabFi -> ShowS
[TabFi] -> ShowS
TabFi -> String
(Int -> TabFi -> ShowS)
-> (TabFi -> String) -> ([TabFi] -> ShowS) -> Show TabFi
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TabFi] -> ShowS
$cshowList :: [TabFi] -> ShowS
show :: TabFi -> String
$cshow :: TabFi -> String
showsPrec :: Int -> TabFi -> ShowS
$cshowsPrec :: Int -> TabFi -> ShowS
Show, ReadPrec [TabFi]
ReadPrec TabFi
Int -> ReadS TabFi
ReadS [TabFi]
(Int -> ReadS TabFi)
-> ReadS [TabFi]
-> ReadPrec TabFi
-> ReadPrec [TabFi]
-> Read TabFi
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TabFi]
$creadListPrec :: ReadPrec [TabFi]
readPrec :: ReadPrec TabFi
$creadPrec :: ReadPrec TabFi
readList :: ReadS [TabFi]
$creadList :: ReadS [TabFi]
readsPrec :: Int -> ReadS TabFi
$creadsPrec :: Int -> ReadS TabFi
Read)
instance Default TabFi where
def :: TabFi
def = Int -> [(Int, Int)] -> [(String, Int)] -> TabFi
fineFi Int
13
[(Int
idLins, Int
11), (Int
idExps, Int
11), (Int
idConsts, Int
9), (Int
idSplines, Int
11), (Int
idStartEnds, Int
12), (Int
idExpsBreakPoints, Int
11), (Int
idLinsBreakPoints, Int
11), (Int
idRandDists, Int
6)]
[(String
idPadsynth, Int
18), (String
idSone, Int
14), (String
idTanh, Int
13), (String
idExp, Int
13)]
fineFi :: Int -> [(Int, Int)] -> [(String, Int)] -> TabFi
fineFi :: Int -> [(Int, Int)] -> [(String, Int)] -> TabFi
fineFi Int
n [(Int, Int)]
xs [(String, Int)]
ys = Int -> IntMap Int -> Map String Int -> TabFi
TabFi Int
n ([(Int, Int)] -> IntMap Int
forall a. [(Int, a)] -> IntMap a
IM.fromList [(Int, Int)]
xs) ([(String, Int)] -> Map String Int
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [(String, Int)]
ys)
coarseFi :: Int -> TabFi
coarseFi :: Int -> TabFi
coarseFi Int
n = Int -> IntMap Int -> Map String Int -> TabFi
TabFi Int
n IntMap Int
forall a. IntMap a
IM.empty Map String Int
forall k a. Map k a
M.empty
idWavs, idMp3s, idDoubles, idSines, idSines3, idSines2,
idPartials, idSines4, idBuzzes, idConsts, idLins, idCubes,
idExps, idSplines, idStartEnds, idPolys, idChebs1, idChebs2, idBessels, idWins,
idTabHarmonics, idMixOnTab, idMixTabs,
idNormTab, idPolynomFuns, idLinTab, idRandDists, idReadNumFile, idReadNumTab,
idExpsBreakPoints, idLinsBreakPoints, idReadTrajectoryFile, idMixSines1, idMixSines2,
idRandHist, idRandPairs, idRandRanges, idPvocex, idTuning, idMultichannel :: Int
idWavs :: Int
idWavs = Int
1
idDoubles :: Int
idDoubles = Int
2
idSines :: Int
idSines = Int
10
idSines3 :: Int
idSines3 = Int
9
idSines2 :: Int
idSines2 = Int
9
idPartials :: Int
idPartials = Int
9
idSines4 :: Int
idSines4 = Int
19
idBuzzes :: Int
idBuzzes = Int
11
idConsts :: Int
idConsts = Int
17
idLins :: Int
idLins = Int
7
idCubes :: Int
idCubes = Int
6
idExps :: Int
idExps = Int
5
idStartEnds :: Int
idStartEnds = Int
16
idSplines :: Int
idSplines = Int
8
idPolys :: Int
idPolys = Int
3
idChebs1 :: Int
idChebs1 = Int
13
idChebs2 :: Int
idChebs2 = Int
14
idBessels :: Int
idBessels = Int
12
idWins :: Int
idWins = Int
20
idMp3s :: Int
idMp3s = Int
49
idTabHarmonics :: Int
idTabHarmonics = Int
30
idMixOnTab :: Int
idMixOnTab = Int
31
idMixTabs :: Int
idMixTabs = Int
32
idNormTab :: Int
idNormTab = Int
4
idLinTab :: Int
idLinTab = Int
18
idRandDists :: Int
idRandDists = Int
21
idReadNumFile :: Int
idReadNumFile = Int
23
idReadNumTab :: Int
idReadNumTab = Int
24
idExpsBreakPoints :: Int
idExpsBreakPoints = Int
25
idLinsBreakPoints :: Int
idLinsBreakPoints = Int
27
idReadTrajectoryFile :: Int
idReadTrajectoryFile = Int
28
idMixSines1 :: Int
idMixSines1 = Int
33
idMixSines2 :: Int
idMixSines2 = Int
34
idRandHist :: Int
idRandHist = Int
40
idRandPairs :: Int
idRandPairs = Int
41
idRandRanges :: Int
idRandRanges = Int
42
idPvocex :: Int
idPvocex = Int
43
idTuning :: Int
idTuning = Int
51
idMultichannel :: Int
idMultichannel = Int
52
idTanh :: String
idTanh = String
"tanh"
idExp :: String
idExp = String
"exp"
idSone :: String
idSone = String
"sone"
idFarey :: String
idFarey = String
"farey"
idWave :: String
idWave = String
"wave"
idPadsynth, idTanh, idExp, idSone, idFarey, idWave :: String
idPadsynth :: String
idPadsynth = String
"padsynth"
idPolynomFuns :: Int
idPolynomFuns = Int
15
type JackoConnect = (String, String)
data Jacko = Jacko
{ Jacko -> String
jackoClient :: String
, Jacko -> String
jackoServer :: String
, Jacko -> [(String, String)]
jackoAudioIns :: [JackoConnect]
, Jacko -> [(String, String)]
jackoAudioOuts :: [JackoConnect]
, Jacko -> [(String, String)]
jackoMidiIns :: [JackoConnect]
, Jacko -> [(String, String)]
jackoMidiOuts :: [JackoConnect]
, Jacko -> Bool
jackoFreewheel :: Bool
, Jacko -> Bool
jackoInfo :: Bool
} deriving (Jacko -> Jacko -> Bool
(Jacko -> Jacko -> Bool) -> (Jacko -> Jacko -> Bool) -> Eq Jacko
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Jacko -> Jacko -> Bool
$c/= :: Jacko -> Jacko -> Bool
== :: Jacko -> Jacko -> Bool
$c== :: Jacko -> Jacko -> Bool
Eq, Int -> Jacko -> ShowS
[Jacko] -> ShowS
Jacko -> String
(Int -> Jacko -> ShowS)
-> (Jacko -> String) -> ([Jacko] -> ShowS) -> Show Jacko
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Jacko] -> ShowS
$cshowList :: [Jacko] -> ShowS
show :: Jacko -> String
$cshow :: Jacko -> String
showsPrec :: Int -> Jacko -> ShowS
$cshowsPrec :: Int -> Jacko -> ShowS
Show, ReadPrec [Jacko]
ReadPrec Jacko
Int -> ReadS Jacko
ReadS [Jacko]
(Int -> ReadS Jacko)
-> ReadS [Jacko]
-> ReadPrec Jacko
-> ReadPrec [Jacko]
-> Read Jacko
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Jacko]
$creadListPrec :: ReadPrec [Jacko]
readPrec :: ReadPrec Jacko
$creadPrec :: ReadPrec Jacko
readList :: ReadS [Jacko]
$creadList :: ReadS [Jacko]
readsPrec :: Int -> ReadS Jacko
$creadsPrec :: Int -> ReadS Jacko
Read)
instance Default Jacko where
def :: Jacko
def = Jacko :: String
-> String
-> [(String, String)]
-> [(String, String)]
-> [(String, String)]
-> [(String, String)]
-> Bool
-> Bool
-> Jacko
Jacko
{ jackoClient :: String
jackoClient = String
"csound-exp"
, jackoServer :: String
jackoServer = String
"default"
, jackoAudioIns :: [(String, String)]
jackoAudioIns = []
, jackoAudioOuts :: [(String, String)]
jackoAudioOuts = []
, jackoMidiIns :: [(String, String)]
jackoMidiIns = []
, jackoMidiOuts :: [(String, String)]
jackoMidiOuts = []
, jackoFreewheel :: Bool
jackoFreewheel = Bool
False
, jackoInfo :: Bool
jackoInfo = Bool
False }
renderJacko :: Jacko -> String
renderJacko :: Jacko -> String
renderJacko Jacko
spec = [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter ( String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
"")
[ String
"JackoInit " String -> ShowS
forall a. [a] -> [a] -> [a]
++ (ShowS
forall a. Show a => a -> String
show ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ Jacko -> String
jackoServer Jacko
spec) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
", " String -> ShowS
forall a. [a] -> [a] -> [a]
++ (ShowS
forall a. Show a => a -> String
show ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ Jacko -> String
jackoClient Jacko
spec)
, if (Jacko -> Bool
jackoFreewheel Jacko
spec) then String
"JackoFreewheel 1" else String
""
, if (Jacko -> Bool
jackoInfo Jacko
spec) then String
"JackoInfo" else String
""
, String -> [(String, String)] -> String
forall a a. (Show a, Show a) => String -> [(a, a)] -> String
renderConnections String
"JackoAudioInConnect" ([(String, String)] -> String) -> [(String, String)] -> String
forall a b. (a -> b) -> a -> b
$ Jacko -> [(String, String)]
jackoAudioIns Jacko
spec
, String -> [(String, String)] -> String
forall a a. (Show a, Show a) => String -> [(a, a)] -> String
renderConnections String
"JackoAudioOutConnect" ([(String, String)] -> String) -> [(String, String)] -> String
forall a b. (a -> b) -> a -> b
$ Jacko -> [(String, String)]
jackoAudioOuts Jacko
spec
, String -> [(String, String)] -> String
forall a a. (Show a, Show a) => String -> [(a, a)] -> String
renderConnections String
"JackoMidiInConnect" ([(String, String)] -> String) -> [(String, String)] -> String
forall a b. (a -> b) -> a -> b
$ Jacko -> [(String, String)]
jackoMidiIns Jacko
spec
, String -> [(String, String)] -> String
forall a a. (Show a, Show a) => String -> [(a, a)] -> String
renderConnections String
"JackoMidiOutConnect" ([(String, String)] -> String) -> [(String, String)] -> String
forall a b. (a -> b) -> a -> b
$ Jacko -> [(String, String)]
jackoMidiOuts Jacko
spec
, String
"JackoOn" ]
where
renderConnections :: String -> [(a, a)] -> String
renderConnections String
name [(a, a)]
links = [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ ((a, a) -> String) -> [(a, a)] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (String -> (a, a) -> String
forall a a. (Show a, Show a) => String -> (a, a) -> String
renderLink String
name) [(a, a)]
links
renderLink :: String -> (a, a) -> String
renderLink String
name (a
a, a
b) = String
name String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ (a -> String
forall a. Show a => a -> String
show a
a) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
", " String -> ShowS
forall a. [a] -> [a] -> [a]
++ (a -> String
forall a. Show a => a -> String
show a
b)
csdNeedTrace :: Options -> Bool
csdNeedTrace :: Options -> Bool
csdNeedTrace Options
opt = Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe Bool
False (Maybe Bool -> Bool) -> Maybe Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Options -> Maybe Bool
csdTrace Options
opt