Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Stream = Stream {}
- type PatId = String
- data Cx = Cx {}
- data StampStyle
- data Schedule
- = Pre StampStyle
- | Live
- data Target = Target {}
- data Args
- data OSC
- data PlayState = PlayState {
- pattern :: ControlPattern
- mute :: Bool
- solo :: Bool
- history :: [ControlPattern]
- type PlayMap = Map PatId PlayState
- sDefault :: String -> Maybe Value
- fDefault :: Double -> Maybe Value
- rDefault :: Rational -> Maybe Value
- iDefault :: Int -> Maybe Value
- bDefault :: Bool -> Maybe Value
- xDefault :: [Word8] -> Maybe Value
- required :: Maybe Value
- superdirtTarget :: Target
- superdirtShape :: OSC
- dirtTarget :: Target
- dirtShape :: OSC
- startStream :: Config -> [(Target, [OSC])] -> IO Stream
- sendHandshakes :: Stream -> IO ()
- sendO :: Bool -> Maybe UDP -> Cx -> Message -> IO ()
- sendBndl :: Bool -> Maybe UDP -> Cx -> Bundle -> IO ()
- resolve :: String -> String -> IO AddrInfo
- startTidal :: Target -> Config -> IO Stream
- startMulti :: [Target] -> Config -> IO ()
- toDatum :: Value -> Datum
- toData :: OSC -> Event ValueMap -> Maybe [Datum]
- substitutePath :: String -> ValueMap -> Maybe String
- getString :: ValueMap -> String -> Maybe String
- playStack :: PlayMap -> ControlPattern
- toOSC :: Double -> [Int] -> Event ValueMap -> Tempo -> OSC -> [(Double, Bool, Message)]
- doCps :: MVar Tempo -> (Double, Maybe Value) -> IO ()
- onTick :: Stream -> State -> IO ()
- processCps :: Tempo -> [Event ValueMap] -> ([(Tempo, Event ValueMap)], Tempo)
- streamOnce :: Stream -> ControlPattern -> IO ()
- streamFirst :: Stream -> ControlPattern -> IO ()
- doTick :: Bool -> Stream -> State -> IO ()
- setPreviousPatternOrSilence :: Stream -> IO ()
- send :: Maybe UDP -> Cx -> (Double, Bool, Message) -> IO ()
- sched :: Tempo -> Rational -> Double
- streamNudgeAll :: Stream -> Double -> IO ()
- streamResetCycles :: Stream -> IO ()
- hasSolo :: Map k PlayState -> Bool
- streamList :: Stream -> IO ()
- streamReplace :: Show a => Stream -> a -> ControlPattern -> IO ()
- streamMute :: Show a => Stream -> a -> IO ()
- streamMutes :: Show a => Stream -> [a] -> IO ()
- streamUnmute :: Show a => Stream -> a -> IO ()
- streamSolo :: Show a => Stream -> a -> IO ()
- streamUnsolo :: Show a => Stream -> a -> IO ()
- withPatId :: Stream -> PatId -> (PlayState -> PlayState) -> IO ()
- withPatIds :: Stream -> [PatId] -> (PlayState -> PlayState) -> IO ()
- streamMuteAll :: Stream -> IO ()
- streamHush :: Stream -> IO ()
- streamUnmuteAll :: Stream -> IO ()
- streamAll :: Stream -> (ControlPattern -> ControlPattern) -> IO ()
- streamGet :: Stream -> String -> IO (Maybe Value)
- streamSet :: Valuable a => Stream -> String -> Pattern a -> IO ()
- streamSetI :: Stream -> String -> Pattern Int -> IO ()
- streamSetF :: Stream -> String -> Pattern Double -> IO ()
- streamSetS :: Stream -> String -> Pattern String -> IO ()
- streamSetB :: Stream -> String -> Pattern Bool -> IO ()
- streamSetR :: Stream -> String -> Pattern Rational -> IO ()
- openListener :: Config -> IO (Maybe UDP)
- ctrlResponder :: Int -> Config -> Stream -> IO ()
- verbose :: Config -> String -> IO ()
- recvMessagesTimeout :: Transport t => Double -> t -> IO [Message]
- streamGetcps :: Stream -> IO Time
- streamGetnow :: Stream -> IO Double
Documentation
data StampStyle Source #
Instances
Eq StampStyle Source # | |
Defined in Sound.Tidal.Stream (==) :: StampStyle -> StampStyle -> Bool # (/=) :: StampStyle -> StampStyle -> Bool # | |
Show StampStyle Source # | |
Defined in Sound.Tidal.Stream showsPrec :: Int -> StampStyle -> ShowS # show :: StampStyle -> String # showList :: [StampStyle] -> ShowS # |
PlayState | |
|
superdirtShape :: OSC Source #
dirtTarget :: Target Source #
sendHandshakes :: Stream -> IO () Source #
playStack :: PlayMap -> ControlPattern Source #
streamOnce :: Stream -> ControlPattern -> IO () Source #
streamFirst :: Stream -> ControlPattern -> IO () Source #
doTick :: Bool -> Stream -> State -> IO () Source #
Query the current pattern (contained in argument stream :: Stream
)
for the events in the current arc (contained in argument st :: T.State
),
translate them to OSC messages, and send these.
If an exception occurs during sending, this functions prints a warning and continues, because the likely reason is that the backend (supercollider) isn't running.
If any exception occurs before or outside sending (e.g., while querying the pattern, while computing a message), this function prints a warning and resets the current pattern to the previous one (or to silence if there isn't one) and continues, because the likely reason is that something is wrong with the current pattern.
setPreviousPatternOrSilence :: Stream -> IO () Source #
streamResetCycles :: Stream -> IO () Source #
streamList :: Stream -> IO () Source #
streamReplace :: Show a => Stream -> a -> ControlPattern -> IO () Source #
streamMuteAll :: Stream -> IO () Source #
streamHush :: Stream -> IO () Source #
streamUnmuteAll :: Stream -> IO () Source #
streamAll :: Stream -> (ControlPattern -> ControlPattern) -> IO () Source #