1- {-# LANGUAGE BangPatterns #-}
2- {-# LANGUAGE ConstraintKinds #-}
3- {-# LANGUAGE FlexibleContexts #-}
4- {-# LANGUAGE GeneralizedNewtypeDeriving #-}
5- {-# LANGUAGE ScopedTypeVariables #-}
1+ {-# LANGUAGE ConstraintKinds, GeneralizedNewtypeDeriving, FlexibleContexts, ScopedTypeVariables, BangPatterns #-}
62{-# OPTIONS_GHC -fno-warn-missing-fields #-}
7- {-# LANGUAGE DeriveGeneric #-}
8- {-# LANGUAGE StandaloneDeriving #-}
3+ {-# language DeriveGeneric, StandaloneDeriving #-}
94
105module Sound.Tidal.Stream.Process where
116
@@ -27,43 +22,43 @@ module Sound.Tidal.Stream.Process where
2722 along with this library. If not, see <http://www.gnu.org/licenses/>.
2823-}
2924
30- import Control.Applicative ((<|>) )
25+ import Control.Applicative ((<|>) )
3126import Control.Concurrent.MVar
32- import qualified Control.Exception as E
33- import Control.Monad ( forM_ , when )
34- import Data.Coerce ( coerce )
35- import qualified Data.Map.Strict as Map
36- import Data.Maybe ( catMaybes , fromJust , fromMaybe )
27+ import Control.Monad ( forM_ , when )
28+ import Data.Coerce ( coerce )
29+ import qualified Data.Map.Strict as Map
30+ import Data.Maybe ( fromJust , fromMaybe , catMaybes )
31+ import qualified Control.Exception as E
3732import Foreign.C.Types
38- import System.IO (hPutStrLn , stderr )
33+ import System.IO (hPutStrLn , stderr )
3934
40- import qualified Sound.Osc.Fd as O
35+ import qualified Sound.Osc.Fd as O
4136
42- import Data.List (sortOn )
43- import qualified Sound.Tidal.Clock as Clock
44- import Sound.Tidal.Core (stack , (#) )
37+ import Sound.Tidal.Stream.Config
38+ import Sound.Tidal.Core (stack , (#) )
4539import Sound.Tidal.ID
46- import qualified Sound.Tidal.Link as Link
47- import Sound.Tidal.Params (pS )
40+ import qualified Sound.Tidal.Link as Link
41+ import qualified Sound.Tidal.Clock as Clock
42+ import Sound.Tidal.Params (pS )
4843import Sound.Tidal.Pattern
49- import Sound.Tidal.Show ( )
50- import Sound.Tidal.Stream.Config
51- import Sound.Tidal.Utils ( (!!!) )
44+ import Sound.Tidal.Utils ( (!!!) )
45+ import Data.List ( sortOn )
46+ import Sound.Tidal.Show ( )
5247
53- import Sound.Tidal.Stream.Target
5448import Sound.Tidal.Stream.Types
49+ import Sound.Tidal.Stream.Target
5550
5651data ProcessedEvent =
5752 ProcessedEvent {
58- peHasOnset :: Bool ,
59- peEvent :: Event ValueMap ,
60- peCps :: Link. BPM ,
61- peDelta :: Link. Micros ,
62- peCycle :: Time ,
63- peOnWholeOrPart :: Link. Micros ,
53+ peHasOnset :: Bool ,
54+ peEvent :: Event ValueMap ,
55+ peCps :: Link. BPM ,
56+ peDelta :: Link. Micros ,
57+ peCycle :: Time ,
58+ peOnWholeOrPart :: Link. Micros ,
6459 peOnWholeOrPartOsc :: O. Time ,
65- peOnPart :: Link. Micros ,
66- peOnPartOsc :: O. Time
60+ peOnPart :: Link. Micros ,
61+ peOnPartOsc :: O. Time
6762 }
6863
6964-- | Query the current pattern (contained in argument @stream :: Stream@)
@@ -112,7 +107,7 @@ doTick stateMV playMV globalFMV cxs (st,end) nudge ops =
112107 tes <- processCps ops es'
113108 -- For each OSC target
114109 forM_ cxs $ \ cx@ (Cx target _ oscs _ _ bussesMV) -> do
115- busses <- mapM readMVar bussesMV
110+ busses <- mapM readMVar bussesMV
116111 -- Latency is configurable per target.
117112 -- Latency is only used when sending events live.
118113 let latency = oLatency target
@@ -230,15 +225,15 @@ toData (OSC {args = Named rqrd}) e
230225toData _ _ = Nothing
231226
232227toDatum :: Value -> O. Datum
233- toDatum (VF x) = O. float x
234- toDatum (VN x) = O. float x
235- toDatum (VI x) = O. int32 x
236- toDatum (VS x) = O. string x
237- toDatum (VR x) = O. float $ ((fromRational x) :: Double )
238- toDatum (VB True ) = O. int32 (1 :: Int )
228+ toDatum (VF x) = O. float x
229+ toDatum (VN x) = O. float x
230+ toDatum (VI x) = O. int32 x
231+ toDatum (VS x) = O. string x
232+ toDatum (VR x) = O. float $ ((fromRational x) :: Double )
233+ toDatum (VB True ) = O. int32 (1 :: Int )
239234toDatum (VB False ) = O. int32 (0 :: Int )
240- toDatum (VX xs) = O. Blob $ O. blob_pack xs
241- toDatum _ = error " toDatum: unhandled value"
235+ toDatum (VX xs) = O. Blob $ O. blob_pack xs
236+ toDatum _ = error " toDatum: unhandled value"
242237
243238substitutePath :: String -> ValueMap -> Maybe String
244239substitutePath str cm = parse str
@@ -256,19 +251,19 @@ getString :: ValueMap -> String -> Maybe String
256251getString cm s = (simpleShow <$> Map. lookup param cm) <|> defaultValue dflt
257252 where (param, dflt) = break (== ' =' ) s
258253 simpleShow :: Value -> String
259- simpleShow (VS str) = str
260- simpleShow (VI i) = show i
261- simpleShow (VF f) = show f
262- simpleShow (VN n) = show n
263- simpleShow (VR r) = show r
264- simpleShow (VB b) = show b
265- simpleShow (VX xs) = show xs
266- simpleShow (VState _) = show " <stateful>"
254+ simpleShow (VS str) = str
255+ simpleShow (VI i) = show i
256+ simpleShow (VF f) = show f
257+ simpleShow (VN n) = show n
258+ simpleShow (VR r) = show r
259+ simpleShow (VB b) = show b
260+ simpleShow (VX xs) = show xs
261+ simpleShow (VState _) = show " <stateful>"
267262 simpleShow (VPattern _) = show " <pattern>"
268- simpleShow (VList _) = show " <list>"
263+ simpleShow (VList _) = show " <list>"
269264 defaultValue :: String -> Maybe String
270265 defaultValue (' =' : dfltVal) = Just dfltVal
271- defaultValue _ = Nothing
266+ defaultValue _ = Nothing
272267
273268playStack :: PlayMap -> ControlPattern
274269playStack pMap = stack . (map pattern ) . (filter active) . Map. elems $ pMap
@@ -318,5 +313,5 @@ setPreviousPatternOrSilence playMV =
318313 modifyMVar_ playMV $ return
319314 . Map. map ( \ pMap -> case history pMap of
320315 _: p: ps -> pMap { pattern = p, history = p: ps }
321- _ -> pMap { pattern = silence, history = [silence] }
316+ _ -> pMap { pattern = silence, history = [silence] }
322317 )
0 commit comments