@@ -34,7 +34,8 @@ import Foreign
34
34
import Foreign.C.Types
35
35
import System.IO (hPutStrLn , stderr )
36
36
37
- import qualified Sound.OSC.FD as O
37
+ import qualified Sound.Osc.Fd as O
38
+ import qualified Sound.Osc.Time.Timeout as O
38
39
import qualified Network.Socket as N
39
40
40
41
import Sound.Tidal.Config
@@ -45,7 +46,6 @@ import Sound.Tidal.Params (pS)
45
46
import Sound.Tidal.Pattern
46
47
import qualified Sound.Tidal.Tempo as T
47
48
import Sound.Tidal.Utils ((!!!) )
48
- -- import qualified Sound.OSC.Datum as O
49
49
import Data.List (sortOn )
50
50
import System.Random (getStdRandom , randomR )
51
51
import Sound.Tidal.Show ()
@@ -59,15 +59,15 @@ data Stream = Stream {sConfig :: Config,
59
59
sStateMV :: MVar ValueMap ,
60
60
-- sOutput :: MVar ControlPattern,
61
61
sLink :: Link. AbletonLink ,
62
- sListen :: Maybe O. UDP ,
62
+ sListen :: Maybe O. Udp ,
63
63
sPMapMV :: MVar PlayMap ,
64
64
sActionsMV :: MVar [T. TempoAction ],
65
65
sGlobalFMV :: MVar (ControlPattern -> ControlPattern ),
66
66
sCxs :: [Cx ]
67
67
}
68
68
69
69
data Cx = Cx { cxTarget :: Target ,
70
- cxUDP :: O. UDP ,
70
+ cxUDP :: O. Udp ,
71
71
cxOSCs :: [OSC ],
72
72
cxAddr :: N. AddrInfo ,
73
73
cxBusAddr :: Maybe N. AddrInfo
@@ -256,13 +256,13 @@ sendHandshakes stream = mapM_ sendHandshake $ filter (oHandshake . cxTarget) (sC
256
256
else
257
257
hPutStrLn stderr " Can't handshake with SuperCollider without control port."
258
258
259
- sendO :: Bool -> (Maybe O. UDP ) -> Cx -> O. Message -> IO ()
259
+ sendO :: Bool -> (Maybe O. Udp ) -> Cx -> O. Message -> IO ()
260
260
sendO isBusMsg (Just listen) cx msg = O. sendTo listen (O. Packet_Message msg) (N. addrAddress addr)
261
261
where addr | isBusMsg && isJust (cxBusAddr cx) = fromJust $ cxBusAddr cx
262
262
| otherwise = cxAddr cx
263
263
sendO _ Nothing cx msg = O. sendMessage (cxUDP cx) msg
264
264
265
- sendBndl :: Bool -> (Maybe O. UDP ) -> Cx -> O. Bundle -> IO ()
265
+ sendBndl :: Bool -> (Maybe O. Udp ) -> Cx -> O. Bundle -> IO ()
266
266
sendBndl isBusMsg (Just listen) cx bndl = O. sendTo listen (O. Packet_Bundle bndl) (N. addrAddress addr)
267
267
where addr | isBusMsg && isJust (cxBusAddr cx) = fromJust $ cxBusAddr cx
268
268
| otherwise = cxAddr cx
@@ -546,7 +546,7 @@ setPreviousPatternOrSilence stream =
546
546
-- Send events early using timestamp in the OSC bundle - used by Superdirt
547
547
-- Send events early by adding timestamp to the OSC message - used by Dirt
548
548
-- Send events live by delaying the thread
549
- send :: Maybe O. UDP -> Cx -> Double -> Double -> (Double , Bool , O. Message ) -> IO ()
549
+ send :: Maybe O. Udp -> Cx -> Double -> Double -> (Double , Bool , O. Message ) -> IO ()
550
550
send listen cx latency extraLatency (time, isBusMsg, m)
551
551
| oSchedule target == Pre BundleStamp = sendBndl isBusMsg listen cx $ O. Bundle timeWithLatency [m]
552
552
| oSchedule target == Pre MessageStamp = sendO isBusMsg listen cx $ addtime m
@@ -555,7 +555,7 @@ send listen cx latency extraLatency (time, isBusMsg, m)
555
555
sendO isBusMsg listen cx m
556
556
return ()
557
557
where addtime (O. Message mpath params) = O. Message mpath ((O. int32 sec): ((O. int32 usec): params))
558
- ut = O. ntpr_to_ut timeWithLatency
558
+ ut = O. ntpr_to_posix timeWithLatency
559
559
sec :: Int
560
560
sec = floor ut
561
561
usec :: Int
@@ -659,7 +659,7 @@ streamSetB = streamSet
659
659
streamSetR :: Stream -> String -> Pattern Rational -> IO ()
660
660
streamSetR = streamSet
661
661
662
- openListener :: Config -> IO (Maybe O. UDP )
662
+ openListener :: Config -> IO (Maybe O. Udp )
663
663
openListener c
664
664
| cCtrlListen c = catchAny run (\ _ -> do verbose c " That port isn't available, perhaps another Tidal instance is already listening on that port?"
665
665
return Nothing
@@ -693,16 +693,16 @@ ctrlResponder waits c (stream@(Stream {sListen = Just sock}))
693
693
return ()
694
694
where
695
695
bufferIndices [] = []
696
- bufferIndices (x: xs') | x == (O. ASCII_String $ O. ascii " &controlBusIndices" ) = catMaybes $ takeWhile isJust $ map O. datum_integral xs'
696
+ bufferIndices (x: xs') | x == (O. AsciiString $ O. ascii " &controlBusIndices" ) = catMaybes $ takeWhile isJust $ map O. datum_integral xs'
697
697
| otherwise = bufferIndices xs'
698
698
-- External controller commands
699
699
act (O. Message " /ctrl" (O. Int32 k: v: [] ))
700
700
= act (O. Message " /ctrl" [O. string $ show k,v])
701
- act (O. Message " /ctrl" (O. ASCII_String k: v@ (O. Float _): [] ))
701
+ act (O. Message " /ctrl" (O. AsciiString k: v@ (O. Float _): [] ))
702
702
= add (O. ascii_to_string k) (VF (fromJust $ O. datum_floating v))
703
- act (O. Message " /ctrl" (O. ASCII_String k: O. ASCII_String v: [] ))
703
+ act (O. Message " /ctrl" (O. AsciiString k: O. AsciiString v: [] ))
704
704
= add (O. ascii_to_string k) (VS (O. ascii_to_string v))
705
- act (O. Message " /ctrl" (O. ASCII_String k: O. Int32 v: [] ))
705
+ act (O. Message " /ctrl" (O. AsciiString k: O. Int32 v: [] ))
706
706
= add (O. ascii_to_string k) (VI (fromIntegral v))
707
707
-- Stream playback commands
708
708
act (O. Message " /mute" (k: [] ))
@@ -729,7 +729,7 @@ ctrlResponder waits c (stream@(Stream {sListen = Just sock}))
729
729
putMVar (sStateMV stream) $ Map. insert k v sMap
730
730
return ()
731
731
withID :: O. Datum -> (ID -> IO () ) -> IO ()
732
- withID (O. ASCII_String k) func = func $ (ID . O. ascii_to_string) k
732
+ withID (O. AsciiString k) func = func $ (ID . O. ascii_to_string) k
733
733
withID (O. Int32 k) func = func $ (ID . show ) k
734
734
withID _ _ = return ()
735
735
ctrlResponder _ _ _ = return ()
0 commit comments