Skip to content
This repository was archived by the owner on Jun 13, 2025. It is now read-only.

Commit 8d6bf14

Browse files
complete restructuring of the stream module into separate sub modules
1 parent 4e7b4eb commit 8d6bf14

File tree

13 files changed

+937
-769
lines changed

13 files changed

+937
-769
lines changed

src/Sound/Tidal/Context.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,7 @@ import Prelude hiding ((<*), (*>))
2222

2323
import Data.Ratio as C
2424

25-
import Sound.Tidal.Stream.Config as C
25+
import Sound.Tidal.Stream as C
2626
import Sound.Tidal.Control as C
2727
import Sound.Tidal.Core as C
2828
import Sound.Tidal.Params as C
@@ -31,7 +31,6 @@ import Sound.Tidal.Pattern as C
3131
import Sound.Tidal.Scales as C
3232
import Sound.Tidal.Show as C
3333
import Sound.Tidal.Simple as C
34-
import Sound.Tidal.Stream.Stream as C
3534
import Sound.Tidal.Transition as C
3635
import Sound.Tidal.UI as C
3736
import Sound.Tidal.Version as C

src/Sound/Tidal/Safe/Context.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -61,8 +61,9 @@ import Sound.Tidal.ParseBP as C
6161
import Sound.Tidal.Pattern as C
6262
import Sound.Tidal.Scales as C
6363
import Sound.Tidal.Simple as C
64-
import Sound.Tidal.Stream.Stream
65-
(startTidal, superdirtTarget, Target(..))
64+
import Sound.Tidal.Stream.Target (superdirtTarget)
65+
import Sound.Tidal.Stream.Types (Target(..))
66+
import Sound.Tidal.Stream.Main (startTidal)
6667
-- import Sound.Tidal.Transition as C
6768
import Sound.Tidal.UI as C
6869
import Sound.Tidal.Version as C

src/Sound/Tidal/Stream.hs

Lines changed: 35 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,35 @@
1+
module Sound.Tidal.Stream
2+
(module Sound.Tidal.Stream.Config
3+
,module Sound.Tidal.Stream.Types
4+
,module Sound.Tidal.Stream.Process
5+
,module Sound.Tidal.Stream.Target
6+
,module Sound.Tidal.Stream.UI
7+
,module Sound.Tidal.Stream.Listen
8+
,module Sound.Tidal.Stream.Main
9+
) where
10+
11+
import Sound.Tidal.Stream.Config
12+
import Sound.Tidal.Stream.Types
13+
import Sound.Tidal.Stream.Process
14+
import Sound.Tidal.Stream.Target
15+
import Sound.Tidal.Stream.UI
16+
import Sound.Tidal.Stream.Listen
17+
import Sound.Tidal.Stream.Main
18+
19+
{-
20+
Stream.hs - re-exports of all stream modules
21+
Copyright (C) 2020, Alex McLean and contributors
22+
23+
This library is free software: you can redistribute it and/or modify
24+
it under the terms of the GNU General Public License as published by
25+
the Free Software Foundation, either version 3 of the License, or
26+
(at your option) any later version.
27+
28+
This library is distributed in the hope that it will be useful,
29+
but WITHOUT ANY WARRANTY; without even the implied warranty of
30+
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
31+
GNU General Public License for more details.
32+
33+
You should have received a copy of the GNU General Public License
34+
along with this library. If not, see <http://www.gnu.org/licenses/>.
35+
-}

src/Sound/Tidal/Stream/Config.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -24,9 +24,9 @@ data Config = Config {cCtrlListen :: Bool,
2424
cCtrlAddr :: String,
2525
cCtrlPort :: Int,
2626
cCtrlBroadcast :: Bool,
27-
cTempoAddr :: String,
28-
cTempoPort :: Int,
29-
cTempoClientPort :: Int,
27+
-- cTempoAddr :: String,
28+
-- cTempoPort :: Int,
29+
-- cTempoClientPort :: Int,
3030
cVerbose :: Bool,
3131
cClockConfig :: Clock.ClockConfig
3232
}
@@ -36,9 +36,9 @@ defaultConfig = Config {cCtrlListen = True,
3636
cCtrlAddr ="127.0.0.1",
3737
cCtrlPort = 6010,
3838
cCtrlBroadcast = False,
39-
cTempoAddr = "127.0.0.1",
40-
cTempoPort = 9160,
41-
cTempoClientPort = 0, -- choose at random
39+
-- cTempoAddr = "127.0.0.1",
40+
-- cTempoPort = 9160,
41+
-- cTempoClientPort = 0, -- choose at random
4242
cVerbose = True,
4343
cClockConfig = Clock.defaultConfig
4444
}

src/Sound/Tidal/Stream/Listen.hs

Lines changed: 118 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,118 @@
1+
module Sound.Tidal.Stream.Listen where
2+
3+
import Data.Maybe (fromJust, catMaybes, isJust)
4+
import Control.Concurrent.MVar
5+
import Control.Monad (when)
6+
import System.IO (hPutStrLn, stderr)
7+
import qualified Data.Map as Map
8+
import qualified Sound.Osc.Fd as O
9+
import qualified Sound.Osc.Time.Timeout as O
10+
import qualified Network.Socket as N
11+
import qualified Control.Exception as E
12+
13+
import Sound.Tidal.ID
14+
import Sound.Tidal.Pattern
15+
16+
import Sound.Tidal.Stream.Config
17+
import Sound.Tidal.Stream.Types
18+
import Sound.Tidal.Stream.UI
19+
20+
{-
21+
Listen.hs - logic for listening and acting on incoming OSC messages
22+
Copyright (C) 2020, Alex McLean and contributors
23+
24+
This library is free software: you can redistribute it and/or modify
25+
it under the terms of the GNU General Public License as published by
26+
the Free Software Foundation, either version 3 of the License, or
27+
(at your option) any later version.
28+
29+
This library is distributed in the hope that it will be useful,
30+
but WITHOUT ANY WARRANTY; without even the implied warranty of
31+
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
32+
GNU General Public License for more details.
33+
34+
You should have received a copy of the GNU General Public License
35+
along with this library. If not, see <http://www.gnu.org/licenses/>.
36+
-}
37+
38+
39+
openListener :: Config -> IO (Maybe O.Udp)
40+
openListener c
41+
| cCtrlListen c = catchAny run (\_ -> do verbose c "That port isn't available, perhaps another Tidal instance is already listening on that port?"
42+
return Nothing
43+
)
44+
| otherwise = return Nothing
45+
where
46+
run = do sock <- O.udpServer (cCtrlAddr c) (cCtrlPort c)
47+
when (cCtrlBroadcast c) $ N.setSocketOption (O.udpSocket sock) N.Broadcast 1
48+
return $ Just sock
49+
catchAny :: IO a -> (E.SomeException -> IO a) -> IO a
50+
catchAny = E.catch
51+
52+
-- Listen to and act on OSC control messages
53+
ctrlResponder :: Int -> Config -> Stream -> IO ()
54+
ctrlResponder waits c (stream@(Stream {sListen = Just sock}))
55+
= do ms <- recvMessagesTimeout 2 sock
56+
if (null ms)
57+
then do checkHandshake -- there was a timeout, check handshake
58+
ctrlResponder (waits+1) c stream
59+
else do mapM_ act ms
60+
ctrlResponder 0 c stream
61+
where
62+
checkHandshake = do busses <- readMVar (sBusses stream)
63+
when (null busses) $ do when (waits == 0) $ verbose c $ "Waiting for SuperDirt (v.1.7.2 or higher).."
64+
sendHandshakes stream
65+
66+
act (O.Message "/dirt/hello" _) = sendHandshakes stream
67+
act (O.Message "/dirt/handshake/reply" xs) = do prev <- swapMVar (sBusses stream) $ bufferIndices xs
68+
-- Only report the first time..
69+
when (null prev) $ verbose c $ "Connected to SuperDirt."
70+
return ()
71+
where
72+
bufferIndices [] = []
73+
bufferIndices (x:xs') | x == (O.AsciiString $ O.ascii "&controlBusIndices") = catMaybes $ takeWhile isJust $ map O.datum_integral xs'
74+
| otherwise = bufferIndices xs'
75+
-- External controller commands
76+
act (O.Message "/ctrl" (O.Int32 k:v:[]))
77+
= act (O.Message "/ctrl" [O.string $ show k,v])
78+
act (O.Message "/ctrl" (O.AsciiString k:v@(O.Float _):[]))
79+
= add (O.ascii_to_string k) (VF (fromJust $ O.datum_floating v))
80+
act (O.Message "/ctrl" (O.AsciiString k:O.AsciiString v:[]))
81+
= add (O.ascii_to_string k) (VS (O.ascii_to_string v))
82+
act (O.Message "/ctrl" (O.AsciiString k:O.Int32 v:[]))
83+
= add (O.ascii_to_string k) (VI (fromIntegral v))
84+
-- Stream playback commands
85+
act (O.Message "/mute" (k:[]))
86+
= withID k $ streamMute stream
87+
act (O.Message "/unmute" (k:[]))
88+
= withID k $ streamUnmute stream
89+
act (O.Message "/solo" (k:[]))
90+
= withID k $ streamSolo stream
91+
act (O.Message "/unsolo" (k:[]))
92+
= withID k $ streamUnsolo stream
93+
act (O.Message "/muteAll" [])
94+
= streamMuteAll stream
95+
act (O.Message "/unmuteAll" [])
96+
= streamUnmuteAll stream
97+
act (O.Message "/unsoloAll" [])
98+
= streamUnsoloAll stream
99+
act (O.Message "/hush" [])
100+
= streamHush stream
101+
act (O.Message "/silence" (k:[]))
102+
= withID k $ streamSilence stream
103+
act m = hPutStrLn stderr $ "Unhandled OSC: " ++ show m
104+
add :: String -> Value -> IO ()
105+
add k v = do sMap <- takeMVar (sStateMV stream)
106+
putMVar (sStateMV stream) $ Map.insert k v sMap
107+
return ()
108+
withID :: O.Datum -> (ID -> IO ()) -> IO ()
109+
withID (O.AsciiString k) func = func $ (ID . O.ascii_to_string) k
110+
withID (O.Int32 k) func = func $ (ID . show) k
111+
withID _ _ = return ()
112+
ctrlResponder _ _ _ = return ()
113+
114+
verbose :: Config -> String -> IO ()
115+
verbose c s = when (cVerbose c) $ putStrLn s
116+
117+
recvMessagesTimeout :: (O.Transport t) => Double -> t -> IO [O.Message]
118+
recvMessagesTimeout n sock = fmap (maybe [] O.packetMessages) $ O.recvPacketTimeout n sock

src/Sound/Tidal/Stream/Main.hs

Lines changed: 78 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,78 @@
1+
module Sound.Tidal.Stream.Main where
2+
3+
import qualified Data.Map as Map
4+
import qualified Sound.Tidal.Clock as Clock
5+
import Control.Concurrent.MVar
6+
import Control.Concurrent
7+
import System.IO (hPutStrLn, stderr)
8+
9+
10+
import Sound.Tidal.Version (tidal_status_string)
11+
import Sound.Tidal.Stream.Config
12+
import Sound.Tidal.Stream.Types
13+
import Sound.Tidal.Stream.Listen
14+
import Sound.Tidal.Stream.Target
15+
import Sound.Tidal.Stream.Process
16+
import Sound.Tidal.Stream.UI
17+
18+
{-
19+
Main.hs - Start tidals stream, listen and act on incoming messages
20+
Copyright (C) 2020, Alex McLean and contributors
21+
22+
This library is free software: you can redistribute it and/or modify
23+
it under the terms of the GNU General Public License as published by
24+
the Free Software Foundation, either version 3 of the License, or
25+
(at your option) any later version.
26+
27+
This library is distributed in the hope that it will be useful,
28+
but WITHOUT ANY WARRANTY; without even the implied warranty of
29+
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
30+
GNU General Public License for more details.
31+
32+
You should have received a copy of the GNU General Public License
33+
along with this library. If not, see <http://www.gnu.org/licenses/>.
34+
-}
35+
36+
37+
-- Start an instance of Tidal with superdirt OSC
38+
startTidal :: Target -> Config -> IO Stream
39+
startTidal target config = startStream config [(target, [superdirtShape])]
40+
41+
-- Start an instance of Tidal
42+
-- Spawns a thread within Tempo that acts as the clock
43+
-- Spawns a thread that listens to and acts on OSC control messages
44+
startStream :: Config -> [(Target, [OSC])] -> IO Stream
45+
startStream config oscmap = do
46+
sMapMV <- newMVar Map.empty
47+
pMapMV <- newMVar Map.empty
48+
bussesMV <- newMVar []
49+
globalFMV <- newMVar id
50+
51+
tidal_status_string >>= verbose config
52+
verbose config $ "Listening for external controls on " ++ cCtrlAddr config ++ ":" ++ show (cCtrlPort config)
53+
listen <- openListener config
54+
55+
cxs <- getCXs config oscmap
56+
57+
clockRef <- Clock.clocked (cClockConfig config) (doTick sMapMV bussesMV pMapMV globalFMV cxs listen)
58+
59+
let stream = Stream {sConfig = config,
60+
sBusses = bussesMV,
61+
sStateMV = sMapMV,
62+
sClockRef = clockRef,
63+
-- sLink = abletonLink,
64+
sListen = listen,
65+
sPMapMV = pMapMV,
66+
-- sActionsMV = actionsMV,
67+
sGlobalFMV = globalFMV,
68+
sCxs = cxs
69+
}
70+
71+
sendHandshakes stream
72+
73+
-- Spawn a thread to handle OSC control messages
74+
_ <- forkIO $ ctrlResponder 0 config stream
75+
return stream
76+
77+
startMulti :: [Target] -> Config -> IO ()
78+
startMulti _ _ = hPutStrLn stderr $ "startMulti has been removed, please check the latest documentation on tidalcycles.org"

0 commit comments

Comments
 (0)