Skip to content

Commit

Permalink
Revert "Apply stylish-haskell formatting"
Browse files Browse the repository at this point in the history
This reverts commit 491bd1b, reversing
changes made to 9eca1d6.
  • Loading branch information
mindofmatthew committed Apr 19, 2024
1 parent 491bd1b commit c6ef650
Show file tree
Hide file tree
Showing 3 changed files with 86 additions and 92 deletions.
99 changes: 47 additions & 52 deletions src/Sound/Tidal/Stream/Process.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,6 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ConstraintKinds, GeneralizedNewtypeDeriving, FlexibleContexts, ScopedTypeVariables, BangPatterns #-}
{-# OPTIONS_GHC -fno-warn-missing-fields #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# language DeriveGeneric, StandaloneDeriving #-}

module Sound.Tidal.Stream.Process where

Expand All @@ -27,43 +22,43 @@ module Sound.Tidal.Stream.Process where
along with this library. If not, see <http://www.gnu.org/licenses/>.
-}

import Control.Applicative ((<|>))
import Control.Applicative ((<|>))
import Control.Concurrent.MVar
import qualified Control.Exception as E
import Control.Monad (forM_, when)
import Data.Coerce (coerce)
import qualified Data.Map.Strict as Map
import Data.Maybe (catMaybes, fromJust, fromMaybe)
import Control.Monad (forM_, when)
import Data.Coerce (coerce)
import qualified Data.Map.Strict as Map
import Data.Maybe (fromJust, fromMaybe, catMaybes)
import qualified Control.Exception as E
import Foreign.C.Types
import System.IO (hPutStrLn, stderr)
import System.IO (hPutStrLn, stderr)

import qualified Sound.Osc.Fd as O
import qualified Sound.Osc.Fd as O

import Data.List (sortOn)
import qualified Sound.Tidal.Clock as Clock
import Sound.Tidal.Core (stack, (#))
import Sound.Tidal.Stream.Config
import Sound.Tidal.Core (stack, (#))
import Sound.Tidal.ID
import qualified Sound.Tidal.Link as Link
import Sound.Tidal.Params (pS)
import qualified Sound.Tidal.Link as Link
import qualified Sound.Tidal.Clock as Clock
import Sound.Tidal.Params (pS)
import Sound.Tidal.Pattern
import Sound.Tidal.Show ()
import Sound.Tidal.Stream.Config
import Sound.Tidal.Utils ((!!!))
import Sound.Tidal.Utils ((!!!))
import Data.List (sortOn)
import Sound.Tidal.Show ()

import Sound.Tidal.Stream.Target
import Sound.Tidal.Stream.Types
import Sound.Tidal.Stream.Target

data ProcessedEvent =
ProcessedEvent {
peHasOnset :: Bool,
peEvent :: Event ValueMap,
peCps :: Link.BPM,
peDelta :: Link.Micros,
peCycle :: Time,
peOnWholeOrPart :: Link.Micros,
peHasOnset :: Bool,
peEvent :: Event ValueMap,
peCps :: Link.BPM,
peDelta :: Link.Micros,
peCycle :: Time,
peOnWholeOrPart :: Link.Micros,
peOnWholeOrPartOsc :: O.Time,
peOnPart :: Link.Micros,
peOnPartOsc :: O.Time
peOnPart :: Link.Micros,
peOnPartOsc :: O.Time
}

-- | Query the current pattern (contained in argument @stream :: Stream@)
Expand Down Expand Up @@ -112,7 +107,7 @@ doTick stateMV playMV globalFMV cxs (st,end) nudge ops =
tes <- processCps ops es'
-- For each OSC target
forM_ cxs $ \cx@(Cx target _ oscs _ _ bussesMV) -> do
busses <- mapM readMVar bussesMV
busses <- mapM readMVar bussesMV
-- Latency is configurable per target.
-- Latency is only used when sending events live.
let latency = oLatency target
Expand Down Expand Up @@ -230,15 +225,15 @@ toData (OSC {args = Named rqrd}) e
toData _ _ = Nothing

toDatum :: Value -> O.Datum
toDatum (VF x) = O.float x
toDatum (VN x) = O.float x
toDatum (VI x) = O.int32 x
toDatum (VS x) = O.string x
toDatum (VR x) = O.float $ ((fromRational x) :: Double)
toDatum (VB True) = O.int32 (1 :: Int)
toDatum (VF x) = O.float x
toDatum (VN x) = O.float x
toDatum (VI x) = O.int32 x
toDatum (VS x) = O.string x
toDatum (VR x) = O.float $ ((fromRational x) :: Double)
toDatum (VB True) = O.int32 (1 :: Int)
toDatum (VB False) = O.int32 (0 :: Int)
toDatum (VX xs) = O.Blob $ O.blob_pack xs
toDatum _ = error "toDatum: unhandled value"
toDatum (VX xs) = O.Blob $ O.blob_pack xs
toDatum _ = error "toDatum: unhandled value"

substitutePath :: String -> ValueMap -> Maybe String
substitutePath str cm = parse str
Expand All @@ -256,19 +251,19 @@ getString :: ValueMap -> String -> Maybe String
getString cm s = (simpleShow <$> Map.lookup param cm) <|> defaultValue dflt
where (param, dflt) = break (== '=') s
simpleShow :: Value -> String
simpleShow (VS str) = str
simpleShow (VI i) = show i
simpleShow (VF f) = show f
simpleShow (VN n) = show n
simpleShow (VR r) = show r
simpleShow (VB b) = show b
simpleShow (VX xs) = show xs
simpleShow (VState _) = show "<stateful>"
simpleShow (VS str) = str
simpleShow (VI i) = show i
simpleShow (VF f) = show f
simpleShow (VN n) = show n
simpleShow (VR r) = show r
simpleShow (VB b) = show b
simpleShow (VX xs) = show xs
simpleShow (VState _) = show "<stateful>"
simpleShow (VPattern _) = show "<pattern>"
simpleShow (VList _) = show "<list>"
simpleShow (VList _) = show "<list>"
defaultValue :: String -> Maybe String
defaultValue ('=':dfltVal) = Just dfltVal
defaultValue _ = Nothing
defaultValue _ = Nothing

playStack :: PlayMap -> ControlPattern
playStack pMap = stack . (map pattern) . (filter active) . Map.elems $ pMap
Expand Down Expand Up @@ -318,5 +313,5 @@ setPreviousPatternOrSilence playMV =
modifyMVar_ playMV $ return
. Map.map ( \ pMap -> case history pMap of
_:p:ps -> pMap { pattern = p, history = p:ps }
_ -> pMap { pattern = silence, history = [silence] }
_ -> pMap { pattern = silence, history = [silence] }
)
54 changes: 27 additions & 27 deletions src/Sound/Tidal/Stream/Types.hs
Original file line number Diff line number Diff line change
@@ -1,33 +1,33 @@
module Sound.Tidal.Stream.Types where

import Control.Concurrent.MVar
import qualified Data.Map.Strict as Map
import Sound.Tidal.Pattern
import Sound.Tidal.Show ()
import qualified Data.Map.Strict as Map
import Sound.Tidal.Pattern
import Sound.Tidal.Show ()

import qualified Network.Socket as N
import qualified Sound.Osc.Fd as O
import qualified Sound.Osc.Fd as O
import qualified Network.Socket as N

import qualified Sound.Tidal.Clock as Clock
import qualified Sound.Tidal.Clock as Clock

import Sound.Tidal.Stream.Config
import Sound.Tidal.Stream.Config

data Stream = Stream {sConfig :: Config,
sStateMV :: MVar ValueMap,
data Stream = Stream {sConfig :: Config,
sStateMV :: MVar ValueMap,
-- sOutput :: MVar ControlPattern,
sClockRef :: Clock.ClockRef,
sListen :: Maybe O.Udp,
sPMapMV :: MVar PlayMap,
sClockRef :: Clock.ClockRef,
sListen :: Maybe O.Udp,
sPMapMV :: MVar PlayMap,
sGlobalFMV :: MVar (ControlPattern -> ControlPattern),
sCxs :: [Cx]
sCxs :: [Cx]
}

data Cx = Cx {cxTarget :: Target,
cxUDP :: O.Udp,
cxOSCs :: [OSC],
cxAddr :: N.AddrInfo,
data Cx = Cx {cxTarget :: Target,
cxUDP :: O.Udp,
cxOSCs :: [OSC],
cxAddr :: N.AddrInfo,
cxBusAddr :: Maybe N.AddrInfo,
cxBusses :: Maybe (MVar [Int])
cxBusses :: Maybe (MVar [Int])
}

data StampStyle = BundleStamp
Expand All @@ -38,13 +38,13 @@ data Schedule = Pre StampStyle
| Live
deriving (Eq, Show)

data Target = Target {oName :: String,
oAddress :: String,
oPort :: Int,
oBusPort :: Maybe Int,
oLatency :: Double,
oWindow :: Maybe Arc,
oSchedule :: Schedule,
data Target = Target {oName :: String,
oAddress :: String,
oPort :: Int,
oBusPort :: Maybe Int,
oLatency :: Double,
oWindow :: Maybe Arc,
oSchedule :: Schedule,
oHandshake :: Bool
}
deriving Show
Expand All @@ -60,8 +60,8 @@ data OSC = OSC {path :: String,
deriving Show

data PlayState = PlayState {pattern :: ControlPattern,
mute :: Bool,
solo :: Bool,
mute :: Bool,
solo :: Bool,
history :: [ControlPattern]
}
deriving Show
Expand Down
25 changes: 12 additions & 13 deletions src/Sound/Tidal/Stream/UI.hs
Original file line number Diff line number Diff line change
@@ -1,20 +1,19 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE BangPatterns, ScopedTypeVariables #-}
module Sound.Tidal.Stream.UI where

import qualified Data.Map as Map
import qualified Control.Exception as E
import Control.Concurrent.MVar
import qualified Control.Exception as E
import qualified Data.Map as Map
import System.IO (hPutStrLn, stderr)
import System.Random (getStdRandom, randomR)
import System.IO (hPutStrLn, stderr)
import System.Random (getStdRandom, randomR)

import qualified Sound.Tidal.Clock as Clock
import qualified Sound.Tidal.Clock as Clock
import Sound.Tidal.Stream.Types
import Sound.Tidal.Stream.Config
import Sound.Tidal.Stream.Process
import Sound.Tidal.Stream.Types

import Sound.Tidal.ID
import Sound.Tidal.Pattern
import Sound.Tidal.ID

streamNudgeAll :: Stream -> Double -> IO ()
streamNudgeAll s = Clock.setNudge (sClockRef s)
Expand Down Expand Up @@ -51,10 +50,10 @@ streamList s = do pMap <- readMVar (sPMapMV s)
let hs = hasSolo pMap
putStrLn $ concatMap (showKV hs) $ Map.toList pMap
where showKV :: Bool -> (PatId, PlayState) -> String
showKV True (k, (PlayState {solo = True})) = k ++ " - solo\n"
showKV True (k, _) = "(" ++ k ++ ")\n"
showKV True (k, (PlayState {solo = True})) = k ++ " - solo\n"
showKV True (k, _) = "(" ++ k ++ ")\n"
showKV False (k, (PlayState {solo = False})) = k ++ "\n"
showKV False (k, _) = "(" ++ k ++ ") - muted\n"
showKV False (k, _) = "(" ++ k ++ ") - muted\n"

streamReplace :: Stream -> ID -> ControlPattern -> IO ()
streamReplace stream k !pat = do
Expand Down Expand Up @@ -138,4 +137,4 @@ streamSetB :: Stream -> String -> Pattern Bool -> IO ()
streamSetB = streamSet

streamSetR :: Stream -> String -> Pattern Rational -> IO ()
streamSetR = streamSet
streamSetR = streamSet

0 comments on commit c6ef650

Please sign in to comment.